From aa689119c7e17de2f8789a1f37ffe27916e726e9 Mon Sep 17 00:00:00 2001 From: Francesco Gazzetta Date: Sun, 11 Jul 2021 17:13:44 +0200 Subject: [PATCH 01/23] Add sourcehut prototype --- haskell-ci.cabal | 2 + src/HaskellCI.hs | 111 +++++++++++++++++++++ src/HaskellCI/Cli.hs | 21 ++++ src/HaskellCI/Sourcehut.hs | 172 ++++++++++++++++++++++++++++++++ src/HaskellCI/Sourcehut/Yaml.hs | 66 ++++++++++++ 5 files changed, 372 insertions(+) create mode 100644 src/HaskellCI/Sourcehut.hs create mode 100644 src/HaskellCI/Sourcehut/Yaml.hs diff --git a/haskell-ci.cabal b/haskell-ci.cabal index 59b40c7a..327fb307 100644 --- a/haskell-ci.cabal +++ b/haskell-ci.cabal @@ -107,6 +107,8 @@ library haskell-ci-internal HaskellCI.Prelude HaskellCI.Sh HaskellCI.ShVersionRange + HaskellCI.Sourcehut + HaskellCI.Sourcehut.Yaml HaskellCI.TestedWith HaskellCI.Tools HaskellCI.Travis diff --git a/src/HaskellCI.hs b/src/HaskellCI.hs index 64beeb9d..90286a3f 100644 --- a/src/HaskellCI.hs +++ b/src/HaskellCI.hs @@ -1,6 +1,8 @@ {-# LANGUAGE DataKinds #-} {-# LANGUAGE MultiWayIf #-} +{-# LANGUAGE NamedFieldPuns #-} {-# LANGUAGE OverloadedStrings #-} +{-# LANGUAGE RecordWildCards #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeApplications #-} @@ -29,9 +31,11 @@ import HaskellCI.Prelude import Control.Exception (try) import Data.List (nubBy, sort, sortBy, (\\)) +import qualified Data.Map.Strict as M import System.Directory (createDirectoryIfMissing, doesFileExist, setCurrentDirectory) import System.Environment (getArgs) import System.Exit (ExitCode (..), exitFailure) +import System.FilePath (()) import System.FilePath.Posix (takeDirectory) import System.IO (hClose, hPutStrLn, stderr) import System.IO.Temp (withSystemTempFile) @@ -46,6 +50,7 @@ import qualified Data.ByteString as BS import qualified Data.List.NonEmpty as NE import qualified Data.Map as Map import qualified Data.Set as S +import qualified Data.Text as TS import qualified Data.Traversable as T import qualified Distribution.Compiler as Compiler import qualified Distribution.Package as Pkg @@ -64,6 +69,8 @@ import HaskellCI.GitHub import HaskellCI.HeadHackage import HaskellCI.Jobs import HaskellCI.Package +import HaskellCI.Sourcehut +import HaskellCI.Sourcehut.Yaml (sourcehutManifests) import HaskellCI.TestedWith import HaskellCI.Travis import HaskellCI.VersionInfo @@ -93,10 +100,12 @@ main = do regenerateBash opts regenerateGitHub opts regenerateTravis opts + regenerateSourcehut opts CommandBash f -> doBash argv0 f opts CommandGitHub f -> doGitHub argv0 f opts CommandTravis f -> doTravis argv0 f opts + CommandSourcehut srhtOpts -> doSourcehut argv0 srhtOpts opts CommandVersionInfo -> do putStrLn $ "haskell-ci " ++ haskellCIVerStr ++ " with dependencies" @@ -368,6 +377,108 @@ regenerateGitHub opts = do noGitHubScript :: IO () noGitHubScript = putStrLn $ "No " ++ fp ++ ", skipping GitHub config regeneration" +------------------------------------------------------------------------------- +-- Sourcehut +------------------------------------------------------------------------------- + +defaultSourcehutPath :: FilePath +defaultSourcehutPath = ".builds" + +doSourcehut :: [String] -> SourcehutOptions (Maybe String) -> Options -> IO () +doSourcehut args srhtOpts opts = do + contents <- sourcehutFromConfigFile args opts srhtOpts + case optOutput opts of + Nothing -> do + createDir defaultSourcehutPath + for_ (M.toList contents) $ \(fn, content) -> + BS.writeFile (defaultSourcehutPath (fn ++ ".yml")) content + Just OutputStdout -> case M.toList contents of + [(_,content)] -> BS.putStr content + _ -> fail "Cannot print multiple files to standard output" + Just (OutputFile fp) -> do + createDir fp + for_ (M.toList contents) $ \(fn, content) -> + BS.writeFile (fp (fn ++ ".yml")) content + where + createDir p = createDirectoryIfMissing True p + +sourcehutFromConfigFile + :: forall m. (MonadIO m, MonadDiagnostics m, MonadMask m) + => [String] + -> Options + -> SourcehutOptions (Maybe String) + -> m (M.Map FilePath ByteString) +sourcehutFromConfigFile args opts srhtOpts@SourcehutOptions{sourcehutOptPath} = do + gitconfig <- liftIO readGitConfig + cabalFiles <- getCabalFiles (optInputType' opts sourcehutOptPath) sourcehutOptPath + config' <- findConfigFile (optConfig opts) + let config = optConfigMorphism opts config' + pkgs <- T.mapM (configFromCabalFile config) cabalFiles + (ghcs, prj) <- case checkVersions (cfgTestedWith config) pkgs of + Right x -> return x + Left [] -> putStrLnErr "panic: checkVersions failed without errors" + Left (e:es) -> putStrLnErrs (e :| es) + + let prj' | cfgGhcHead config = over (mapped . field @"pkgJobs") (S.insert GHCHead) prj + | otherwise = prj + + ls <- genSourcehutFromConfigs args config gitconfig srhtOpts prj' ghcs + return ls -- TODO patchSourcehut config ls + +genSourcehutFromConfigs + :: (Monad m, MonadIO m, MonadDiagnostics m) + => [String] + -> Config + -> GitConfig + -> SourcehutOptions (Maybe String) + -> Project URI Void Package + -> Set CompilerVersion + -> m (M.Map FilePath ByteString) +genSourcehutFromConfigs argv config gitconfig SourcehutOptions{..} prj vs = do + let jobVersions = makeJobVersions config vs + gitRemote = case M.toList (gitCfgRemotes gitconfig) of + [(_,url)] -> Just url + _ -> Nothing -- TODO handle multiple remotes (pick origin?) + sourcehutOptSource' <- case sourcehutOptSource of + Just url -> return url + Nothing -> case gitRemote of + Just url -> return $ TS.unpack url + Nothing -> putStrLnErr "multiple/no remotes found and --sourcehut-source was not used" + let srhtOpts = SourcehutOptions{sourcehutOptSource = sourcehutOptSource',..} + case makeSourcehut argv config srhtOpts prj jobVersions of + Left err -> putStrLnErr $ displayException err + Right sourcehut -> do + describeJobs "Sourcehut config" (cfgTestedWith config) jobVersions (prjPackages prj) + return $ toUTF8BS . prettyYaml id . reann (sourcehutHeader (cfgInsertVersion config) argv ++) . toYaml + <$> sourcehutManifests sourcehut + +regenerateSourcehut :: Options -> IO () +regenerateSourcehut opts = do + -- change the directory + for_ (optCwd opts) setCurrentDirectory + + -- read, and then change to the directory + withContents fp noSourcehutScript $ \contents -> case findRegendataArgv contents of + Nothing -> do + hPutStrLn stderr $ "Error: expected REGENDATA line in " ++ fp + exitFailure + + Just (mversion, argv) -> do + -- warn if we regenerate using older haskell-ci + for_ mversion $ \version -> for_ (simpleParsec haskellCIVerStr) $ \haskellCIVer -> + when (haskellCIVer < version) $ do + hPutStrLn stderr $ "Regenerating using older haskell-ci-" ++ haskellCIVerStr + hPutStrLn stderr $ "File generated using haskell-ci-" ++ prettyShow version + + (srhtOpts, opts') <- parseOptionsSrht argv + -- TODO delete existing .yml files + doSourcehut argv srhtOpts ( optionsWithOutputFile fp <> opts' <> opts) + where + fp = defaultSourcehutPath -- TODO get any of the .yml files in this directory + + noSourcehutScript :: IO () + noSourcehutScript = putStrLn $ "No " ++ fp ++ ", skipping Sourcehut config regeneration" + ------------------------------------------------------------------------------- -- Config file ------------------------------------------------------------------------------- diff --git a/src/HaskellCI/Cli.hs b/src/HaskellCI/Cli.hs index ce10fea8..b3c0e37a 100644 --- a/src/HaskellCI/Cli.hs +++ b/src/HaskellCI/Cli.hs @@ -5,6 +5,7 @@ module HaskellCI.Cli where import HaskellCI.Prelude +import Control.Applicative (optional) import System.Exit (exitFailure) import System.FilePath.Posix (takeFileName) import System.IO (hPutStrLn, stderr) @@ -13,6 +14,7 @@ import qualified Options.Applicative as O import HaskellCI.Config import HaskellCI.OptparseGrammar +import HaskellCI.Sourcehut (SourcehutOptions(..)) import HaskellCI.VersionInfo ------------------------------------------------------------------------------- @@ -23,6 +25,7 @@ data Command = CommandTravis FilePath | CommandBash FilePath | CommandGitHub FilePath + | CommandSourcehut (SourcehutOptions (Maybe String)) | CommandRegenerate | CommandListGHC | CommandDumpConfig @@ -133,6 +136,7 @@ cliParserInfo = O.info ((,) <$> cmdP <*> optionsP O.<**> versionP O.<**> O.helpe , O.command "travis" $ O.info travisP $ O.progDesc "Generate travis-ci config" , O.command "bash" $ O.info bashP $ O.progDesc "Generate local-bash-docker script" , O.command "github" $ O.info githubP $ O.progDesc "Generate GitHub Actions config" + , O.command "sourcehut" $ O.info sourcehutP $ O.progDesc "Generate Sourcehut config" , O.command "list-ghc" $ O.info (pure CommandListGHC) $ O.progDesc "List known GHC versions" , O.command "dump-config" $ O.info (pure CommandDumpConfig) $ O.progDesc "Dump cabal.haskell-ci config with default values" , O.command "version-info" $ O.info (pure CommandVersionInfo) $ O.progDesc "Print versions info haskell-ci was compiled with" @@ -147,6 +151,11 @@ cliParserInfo = O.info ((,) <$> cmdP <*> optionsP O.<**> versionP O.<**> O.helpe githubP = CommandGitHub <$> O.strArgument (O.metavar "CABAL.FILE" <> O.action "file" <> O.help "Either or cabal.project") + sourcehutP = fmap CommandSourcehut $ SourcehutOptions + <$> O.strArgument (O.metavar "CABAL.FILE" <> O.action "file" <> O.help "Either or cabal.project") + <*> optional (O.strOption (O.long "source" <> O.metavar "URI" <> O.help "The source to test (default: from git remote)")) + <*> O.switch (O.long "sourcehut-parallel" <> O.help "In Sourcehut, use many manifests to run jobs in parallel") + ------------------------------------------------------------------------------- -- Parsing helpers ------------------------------------------------------------------------------- @@ -166,4 +175,16 @@ parseOptions argv = case res of fromCmd (CommandTravis fp) = return fp fromCmd (CommandBash fp) = return fp fromCmd (CommandGitHub fp) = return fp + fromCmd (CommandSourcehut srhtOpts) = return $ sourcehutOptPath srhtOpts fromCmd cmd = fail $ "Command without filepath: " ++ show cmd + +-- TODO find a way to merge this with the above... or use global options only +parseOptionsSrht :: [String] -> IO (SourcehutOptions (Maybe String), Options) +parseOptionsSrht argv = case res of + O.Success (CommandSourcehut cmd, opts) -> return (cmd, opts) + O.Success _ -> fail "parseOptionsSrht on non-sourcehut command" + O.Failure f -> case O.renderFailure f "haskell-ci" of + (help, _) -> hPutStrLn stderr help >> exitFailure + O.CompletionInvoked _ -> exitFailure -- unexpected + where + res = O.execParserPure (O.prefs O.subparserInline) cliParserInfo argv diff --git a/src/HaskellCI/Sourcehut.hs b/src/HaskellCI/Sourcehut.hs new file mode 100644 index 00000000..e7515012 --- /dev/null +++ b/src/HaskellCI/Sourcehut.hs @@ -0,0 +1,172 @@ +-- | Take configuration, produce 'Sourcehut'. +{-# LANGUAGE NamedFieldPuns #-} +{-# LANGUAGE OverloadedStrings #-} +{-# LANGUAGE RecordWildCards #-} +module HaskellCI.Sourcehut ( + SourcehutOptions(..), + makeSourcehut, + sourcehutHeader, + ) where + +import HaskellCI.Prelude + +import Data.Bifunctor (first) +import qualified Data.Map.Strict as M +import qualified Data.Set as S +import qualified Distribution.Fields.Pretty as C +import qualified Distribution.Package as C +import qualified Distribution.Pretty as C +import qualified Distribution.Types.GenericPackageDescription as C +import qualified Distribution.Types.PackageDescription as C +import qualified Distribution.Types.VersionRange as C +import qualified Distribution.Utils.ShortText as C +import qualified Distribution.Version as C +import System.FilePath.Posix (takeFileName) + +import Cabal.Project +import HaskellCI.Auxiliary +import HaskellCI.Compiler +import HaskellCI.Config +import HaskellCI.Config.ConstraintSet +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.Validity +import HaskellCI.HeadHackage +import HaskellCI.Jobs +import HaskellCI.List +import HaskellCI.MonadErr +import HaskellCI.Package +import HaskellCI.Sh +import HaskellCI.ShVersionRange +import HaskellCI.Tools +import HaskellCI.Sourcehut.Yaml +import HaskellCI.VersionInfo + +------------------------------------------------------------------------------- +-- Sourcehut options +------------------------------------------------------------------------------- + +data SourcehutOptions src = SourcehutOptions + { sourcehutOptPath :: FilePath + , sourcehutOptSource :: src + , sourcehutOptParallel :: Bool + } + deriving Show + +------------------------------------------------------------------------------- +-- Sourcehut header +------------------------------------------------------------------------------- + +sourcehutHeader :: Bool -> [String] -> [String] +sourcehutHeader insertVersion argv = + [ "This Sourcehut 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 [] + +------------------------------------------------------------------------------- +-- Generate sourcehut configuration +------------------------------------------------------------------------------- + +{- +Sourcehut–specific notes: + +* We don't use -j for parallelism, as machines could have different numbers of + cores +* By default we run jobs sequentially, since on the sr.ht instance parallelism + is limited and build machines are fast +-} + +makeSourcehut + :: [String] + -> Config + -> SourcehutOptions String + -> Project URI Void Package + -> JobVersions + -> Either HsCiError Sourcehut +makeSourcehut argv config@Config{..} SourcehutOptions{..} prj JobVersions{linuxVersions} = do + return $ Sourcehut $ + if sourcehutOptParallel + then parallelManifests + else M.singleton "all" sequentialManifest + where + parallelManifests = M.mapKeys dispGhcVersionShort $ + M.fromSet (mkManifest . S.singleton) linuxVersions + sequentialManifest = mkManifest linuxVersions + mkManifest jobs = SourcehutManifest + { srhtManifestImage = cfgUbuntu + , srhtManifestPackages = "gcc" : "cabal-install-3.4" : (dispGhcVersion <$> S.toList jobs) + , srhtManifestRepositories = M.singleton + "hvr-ghc" + ("http://ppa.launchpad.net/hvr/ghc/ubuntu " ++ C.prettyShow cfgUbuntu ++ " main ff3aeacef6f88286") + , srhtManifestArtifacts = ["sdist.tar.gz"] -- TODO sdist (with proper name) and maybe the binary + , srhtManifestSources = [sourcehutOptSource] + , srhtManifestTasks = + [ SourcehutTask "prepare" [ Sh "export PATH=$PATH:/opt/cabal/bin" + , Sh "echo 'export PATH=$PATH:/opt/cabal/bin' >> .buildenv" + , Sh "cabal update" + ] + ] ++ foldMap mkTasks jobs + , srhtManifestTriggers = SourcehutTriggerEmail <$> getEmails prj + , srhtManifestEnvironment = mempty + } + dispGhcVersionTask job = (\c -> if c == '.' then '_' else c) <$> dispGhcVersionShort job + clonePath = takeFileName sourcehutOptSource + cdToClone = Sh $ "cd " ++ clonePath + -- TODO make this like the github/travis/bash ones + mkTasks job = fmap (\(SourcehutTask name code) -> SourcehutTask + (dispGhcVersionTask job ++ "-" ++ name) + (cdToClone : code) + ) + [ SourcehutTask "prepare" + [ Sh $ "cabal configure -w /opt/ghc/bin/" ++ dispGhcVersion job + ] + , SourcehutTask "check" + [ Sh "cabal check" + ] + , SourcehutTask "dependencies" + [ Sh "cabal build all --enable-tests --only-dependencies" + , Sh "cabal build all --only-dependencies" + ] + , SourcehutTask "build" + [ Sh "cabal build all" + ] + , SourcehutTask "test" + [ Sh "cabal test all --enable-tests" + ] + , SourcehutTask "haddock" + [ Sh "cabal haddock all" + ] + , SourcehutTask "sdist" + [ Sh "cabal sdist -o .", Sh "mv *-*.tar.gz ../sdist.tar.gz" + ] + ] + +getEmails :: Project URI Void Package -> [String] +getEmails = fmap (C.fromShortText . C.maintainer . C.packageDescription . pkgGpd) . prjPackages + +sourcehutRun :: String -> ShM () -> ListBuilder (Either HsCiError SourcehutTask) () +sourcehutRun name shm = item $ do + shs <- runSh shm + return $ SourcehutTask name shs + +tell_env' :: String -> String -> String +tell_env' k v = "echo " ++ show ("export" ++ k ++ "=" ++ v) ++ " >> \"~/.buildenv\"" + +tell_env :: String -> String -> ShM () +tell_env k v = sh $ tell_env' k v diff --git a/src/HaskellCI/Sourcehut/Yaml.hs b/src/HaskellCI/Sourcehut/Yaml.hs new file mode 100644 index 00000000..93fdad20 --- /dev/null +++ b/src/HaskellCI/Sourcehut/Yaml.hs @@ -0,0 +1,66 @@ +{-# LANGUAGE OverloadedStrings #-} +{-# LANGUAGE RecordWildCards #-} +{-# LANGUAGE StrictData #-} +-- | @.builds@ structure. +module HaskellCI.Sourcehut.Yaml where + +import HaskellCI.Prelude + +import qualified Data.Aeson as Aeson +import qualified Data.Map.Strict as M + +import HaskellCI.Config.Ubuntu +import HaskellCI.List +import HaskellCI.Sh +import HaskellCI.YamlSyntax + +------------------------------------------------------------------------------- +-- Data +------------------------------------------------------------------------------- + +newtype Sourcehut = Sourcehut + { sourcehutManifests :: M.Map String SourcehutManifest + } + +data SourcehutManifest = SourcehutManifest + { srhtManifestImage :: Ubuntu + , srhtManifestPackages :: [String] + , srhtManifestRepositories :: M.Map String String + , srhtManifestArtifacts :: [FilePath] + , srhtManifestSources :: [String] + , srhtManifestTasks :: [SourcehutTask] + , srhtManifestTriggers :: [SourcehutTrigger] + , srhtManifestEnvironment :: M.Map String String + } + +data SourcehutTask = SourcehutTask String [Sh] + +data SourcehutTrigger = SourcehutTriggerEmail String -- the "to" address + | SourcehutTriggerWebhook String + +instance ToYaml SourcehutManifest where + toYaml SourcehutManifest{..} = ykeyValuesFilt [] + [ "image" ~> fromString ("ubuntu/" ++ showUbuntu srhtManifestImage) + , "packages" ~> ylistFilt [] (fromString <$> srhtManifestPackages) + , "repositories" ~> ykeyValuesFilt [] + ((\(name, src) -> name ~> fromString src) <$> M.toList srhtManifestRepositories) + , "artifacts" ~> ylistFilt [] (fromString <$> srhtManifestArtifacts) + , "sources" ~> ylistFilt [] (fromString <$> srhtManifestSources) + , "tasks" ~> ylistFilt [] + ((\(SourcehutTask name code) -> ykeyValuesFilt [] $ [name ~> fromString (shlistToString code)]) <$> srhtManifestTasks) + , "triggers" ~> ylistFilt [] (toYaml <$> srhtManifestTriggers) + , "environment" ~> ykeyValuesFilt [] + ((\(k, v) -> k ~> fromString v) <$> M.toList srhtManifestEnvironment) + ] + +instance ToYaml SourcehutTrigger where + toYaml (SourcehutTriggerEmail to) = ykeyValuesFilt [] + [ "action" ~> "email" + , "condition" ~> "failure" + , "to" ~> fromString to + ] + toYaml (SourcehutTriggerWebhook url) = ykeyValuesFilt [] + [ "action" ~> "webhook" + , "condition" ~> "failure" + , "url" ~> fromString url + ] From 40886178eebbc1e64fbe43017c7f41851c6f536a Mon Sep 17 00:00:00 2001 From: Francesco Gazzetta Date: Thu, 28 Oct 2021 11:17:11 +0200 Subject: [PATCH 02/23] sourcehut: --no-install-dependencies --- src/HaskellCI/Sourcehut.hs | 52 ++++++++++++++++++++------------------ 1 file changed, 27 insertions(+), 25 deletions(-) diff --git a/src/HaskellCI/Sourcehut.hs b/src/HaskellCI/Sourcehut.hs index e7515012..9f0ed065 100644 --- a/src/HaskellCI/Sourcehut.hs +++ b/src/HaskellCI/Sourcehut.hs @@ -130,31 +130,33 @@ makeSourcehut argv config@Config{..} SourcehutOptions{..} prj JobVersions{linuxV cdToClone = Sh $ "cd " ++ clonePath -- TODO make this like the github/travis/bash ones mkTasks job = fmap (\(SourcehutTask name code) -> SourcehutTask - (dispGhcVersionTask job ++ "-" ++ name) - (cdToClone : code) - ) - [ SourcehutTask "prepare" - [ Sh $ "cabal configure -w /opt/ghc/bin/" ++ dispGhcVersion job - ] - , SourcehutTask "check" - [ Sh "cabal check" - ] - , SourcehutTask "dependencies" - [ Sh "cabal build all --enable-tests --only-dependencies" - , Sh "cabal build all --only-dependencies" - ] - , SourcehutTask "build" - [ Sh "cabal build all" - ] - , SourcehutTask "test" - [ Sh "cabal test all --enable-tests" - ] - , SourcehutTask "haddock" - [ Sh "cabal haddock all" - ] - , SourcehutTask "sdist" - [ Sh "cabal sdist -o .", Sh "mv *-*.tar.gz ../sdist.tar.gz" - ] + (dispGhcVersionTask job ++ "-" ++ name) + (cdToClone : code) + ) $ concat + [ [ SourcehutTask "prepare" + [ Sh $ "cabal configure -w /opt/ghc/bin/" ++ dispGhcVersion job + ] + , SourcehutTask "check" + [ Sh "cabal check" + ] + ] + , (if cfgInstallDeps then (:[]) else const []) $ SourcehutTask "dependencies" + [ Sh "cabal build all --enable-tests --only-dependencies" + , Sh "cabal build all --only-dependencies" + ] + , [ SourcehutTask "build" + [ Sh "cabal build all" + ] + , SourcehutTask "test" + [ Sh "cabal test all --enable-tests" + ] + , SourcehutTask "haddock" + [ Sh "cabal haddock all" + ] + , SourcehutTask "sdist" + [ Sh "cabal sdist -o .", Sh "mv *-*.tar.gz ../sdist.tar.gz" + ] + ] ] getEmails :: Project URI Void Package -> [String] From 2b8fd56e33ea90f2cb7311643a45f47c354d6110 Mon Sep 17 00:00:00 2001 From: Francesco Gazzetta Date: Thu, 28 Oct 2021 14:06:28 +0200 Subject: [PATCH 03/23] sourcehut: fix regenerate command --- src/HaskellCI.hs | 21 ++++++++++++++------- src/HaskellCI/Sourcehut.hs | 10 +++++++--- 2 files changed, 21 insertions(+), 10 deletions(-) diff --git a/src/HaskellCI.hs b/src/HaskellCI.hs index 90286a3f..0ed95c0e 100644 --- a/src/HaskellCI.hs +++ b/src/HaskellCI.hs @@ -30,14 +30,15 @@ module HaskellCI ( import HaskellCI.Prelude import Control.Exception (try) -import Data.List (nubBy, sort, sortBy, (\\)) +import Data.List (nubBy, sort, sortBy, (\\), isSuffixOf) import qualified Data.Map.Strict as M -import System.Directory (createDirectoryIfMissing, doesFileExist, setCurrentDirectory) +import System.Directory (createDirectoryIfMissing, doesFileExist, setCurrentDirectory, getDirectoryContents) import System.Environment (getArgs) import System.Exit (ExitCode (..), exitFailure) import System.FilePath (()) import System.FilePath.Posix (takeDirectory) import System.IO (hClose, hPutStrLn, stderr) +import System.IO.Error (catchIOError, isDoesNotExistError) import System.IO.Temp (withSystemTempFile) import System.Process (readProcessWithExitCode) @@ -457,6 +458,8 @@ regenerateSourcehut opts = do -- change the directory for_ (optCwd opts) setCurrentDirectory + yamls <- filter (isSuffixOf ".yml") <$> getDirectoryContents' defaultSourcehutPath + let fp = case yamls of [] -> ".build.yml"; f : _ -> defaultSourcehutPath f -- read, and then change to the directory withContents fp noSourcehutScript $ \contents -> case findRegendataArgv contents of Nothing -> do @@ -470,14 +473,18 @@ regenerateSourcehut opts = do hPutStrLn stderr $ "Regenerating using older haskell-ci-" ++ haskellCIVerStr hPutStrLn stderr $ "File generated using haskell-ci-" ++ prettyShow version + -- Warn about outdated .yml files. to be safe, we don't delete them all. + putStrLnWarn "Outdated .yml files will not be deleted" (srhtOpts, opts') <- parseOptionsSrht argv - -- TODO delete existing .yml files - doSourcehut argv srhtOpts ( optionsWithOutputFile fp <> opts' <> opts) + doSourcehut argv srhtOpts ( opts' <> opts) where - fp = defaultSourcehutPath -- TODO get any of the .yml files in this directory - noSourcehutScript :: IO () - noSourcehutScript = putStrLn $ "No " ++ fp ++ ", skipping Sourcehut config regeneration" + noSourcehutScript = putStrLn $ "No " ++ defaultSourcehutPath ++ "/*.yml or .build.yml, skipping Sourcehut config regeneration" + getDirectoryContents' :: FilePath -> IO [FilePath] + getDirectoryContents' fp = + getDirectoryContents fp + `catchIOError` + \e -> if isDoesNotExistError e then return [] else ioError e ------------------------------------------------------------------------------- -- Config file diff --git a/src/HaskellCI/Sourcehut.hs b/src/HaskellCI/Sourcehut.hs index 9f0ed065..b76c63c7 100644 --- a/src/HaskellCI/Sourcehut.hs +++ b/src/HaskellCI/Sourcehut.hs @@ -74,10 +74,14 @@ sourcehutHeader insertVersion argv = , "For more information, see https://github.com/haskell-CI/haskell-ci" , "" ] ++ - if insertVersion then - [ "version: " ++ haskellCIVerStr + verlines ++ + [ "REGENDATA " ++ if insertVersion then show (haskellCIVerStr, argv) else show argv , "" - ] else [] + ] + where + verlines + | insertVersion = [ "version: " ++ haskellCIVerStr , "" ] + | otherwise = [] ------------------------------------------------------------------------------- -- Generate sourcehut configuration From 3bbbdf84337b344216ed69f3d8c021e7b8f844ad Mon Sep 17 00:00:00 2001 From: Francesco Gazzetta Date: Wed, 10 Nov 2021 17:53:26 +0100 Subject: [PATCH 04/23] sourcehut: use origin in case of multiple remotes --- src/HaskellCI.hs | 6 +++++- 1 file changed, 5 insertions(+), 1 deletion(-) diff --git a/src/HaskellCI.hs b/src/HaskellCI.hs index 0ed95c0e..69ed6a9d 100644 --- a/src/HaskellCI.hs +++ b/src/HaskellCI.hs @@ -439,7 +439,11 @@ genSourcehutFromConfigs argv config gitconfig SourcehutOptions{..} prj vs = do let jobVersions = makeJobVersions config vs gitRemote = case M.toList (gitCfgRemotes gitconfig) of [(_,url)] -> Just url - _ -> Nothing -- TODO handle multiple remotes (pick origin?) + -- In case of multiple remotes, pick origin + -- MAYBE just pick the first instead? + rs -> case filter (("origin" ==) . fst) rs of + (_,url) : _ -> Just url + [] -> Nothing sourcehutOptSource' <- case sourcehutOptSource of Just url -> return url Nothing -> case gitRemote of From 6e6365c71d21576beec6ecca72e0c6567bc7debf Mon Sep 17 00:00:00 2001 From: Francesco Gazzetta Date: Wed, 10 Nov 2021 19:40:33 +0100 Subject: [PATCH 05/23] sourcehut: use ListBuilder --- src/HaskellCI/Sourcehut.hs | 113 ++++++++++++++++++------------------- 1 file changed, 54 insertions(+), 59 deletions(-) diff --git a/src/HaskellCI/Sourcehut.hs b/src/HaskellCI/Sourcehut.hs index b76c63c7..26844db8 100644 --- a/src/HaskellCI/Sourcehut.hs +++ b/src/HaskellCI/Sourcehut.hs @@ -103,76 +103,71 @@ makeSourcehut -> Project URI Void Package -> JobVersions -> Either HsCiError Sourcehut -makeSourcehut argv config@Config{..} SourcehutOptions{..} prj JobVersions{linuxVersions} = do - return $ Sourcehut $ +makeSourcehut argv config@Config{..} SourcehutOptions{..} prj JobVersions{linuxVersions} = + Sourcehut <$> if sourcehutOptParallel then parallelManifests - else M.singleton "all" sequentialManifest + else M.singleton "all" <$> sequentialManifest where - parallelManifests = M.mapKeys dispGhcVersionShort $ - M.fromSet (mkManifest . S.singleton) linuxVersions + parallelManifests :: Either HsCiError (M.Map String SourcehutManifest) + parallelManifests = fmap (M.mapKeys dispGhcVersionShort) $ + sequence $ M.fromSet (mkManifest . S.singleton) linuxVersions + sequentialManifest :: Either HsCiError SourcehutManifest sequentialManifest = mkManifest linuxVersions - mkManifest jobs = SourcehutManifest - { srhtManifestImage = cfgUbuntu - , srhtManifestPackages = "gcc" : "cabal-install-3.4" : (dispGhcVersion <$> S.toList jobs) - , srhtManifestRepositories = M.singleton - "hvr-ghc" - ("http://ppa.launchpad.net/hvr/ghc/ubuntu " ++ C.prettyShow cfgUbuntu ++ " main ff3aeacef6f88286") - , srhtManifestArtifacts = ["sdist.tar.gz"] -- TODO sdist (with proper name) and maybe the binary - , srhtManifestSources = [sourcehutOptSource] - , srhtManifestTasks = - [ SourcehutTask "prepare" [ Sh "export PATH=$PATH:/opt/cabal/bin" - , Sh "echo 'export PATH=$PATH:/opt/cabal/bin' >> .buildenv" - , Sh "cabal update" - ] - ] ++ foldMap mkTasks jobs - , srhtManifestTriggers = SourcehutTriggerEmail <$> getEmails prj - , srhtManifestEnvironment = mempty - } - dispGhcVersionTask job = (\c -> if c == '.' then '_' else c) <$> dispGhcVersionShort job + mkManifest :: Set CompilerVersion -> Either HsCiError SourcehutManifest + mkManifest jobs = do + prepare <- fmap (SourcehutTask "all-prepare") $ runSh $ do + sh "export PATH=$PATH:/opt/cabal/bin" + tell_env "PATH" "$PATH:/opt/cabal/bin" + sh "cabal update" + tasks <- concat <$> traverse mkTasksForGhc (S.toList jobs) + return SourcehutManifest + { srhtManifestImage = cfgUbuntu + , srhtManifestPackages = "gcc" : "cabal-install-3.4" : (dispGhcVersion <$> S.toList jobs) + , srhtManifestRepositories = M.singleton + "hvr-ghc" + ("http://ppa.launchpad.net/hvr/ghc/ubuntu " ++ C.prettyShow cfgUbuntu ++ " main ff3aeacef6f88286") + , srhtManifestArtifacts = ["sdist.tar.gz"] -- TODO sdist (with proper name) and maybe the binary + , srhtManifestSources = [sourcehutOptSource] + , srhtManifestTasks = prepare : tasks + , srhtManifestTriggers = SourcehutTriggerEmail <$> getEmails prj + , srhtManifestEnvironment = mempty + } clonePath = takeFileName sourcehutOptSource - cdToClone = Sh $ "cd " ++ clonePath - -- TODO make this like the github/travis/bash ones - mkTasks job = fmap (\(SourcehutTask name code) -> SourcehutTask - (dispGhcVersionTask job ++ "-" ++ name) - (cdToClone : code) - ) $ concat - [ [ SourcehutTask "prepare" - [ Sh $ "cabal configure -w /opt/ghc/bin/" ++ dispGhcVersion job - ] - , SourcehutTask "check" - [ Sh "cabal check" - ] - ] - , (if cfgInstallDeps then (:[]) else const []) $ SourcehutTask "dependencies" - [ Sh "cabal build all --enable-tests --only-dependencies" - , Sh "cabal build all --only-dependencies" - ] - , [ SourcehutTask "build" - [ Sh "cabal build all" - ] - , SourcehutTask "test" - [ Sh "cabal test all --enable-tests" - ] - , SourcehutTask "haddock" - [ Sh "cabal haddock all" - ] - , SourcehutTask "sdist" - [ Sh "cabal sdist -o .", Sh "mv *-*.tar.gz ../sdist.tar.gz" - ] - ] - ] + -- MAYBE reader for job and clonePath + mkTasksForGhc :: CompilerVersion -> Either HsCiError [SourcehutTask] + mkTasksForGhc job = sequence $ buildList $ do + sourcehutRun "prepare" job clonePath $ + sh $ "cabal configure -w /opt/ghc/bin/" ++ dispGhcVersion job + sourcehutRun "check" job clonePath $ + sh "cabal check" + when cfgInstallDeps $ sourcehutRun "dependencies" job clonePath $ do + sh "cabal build all --enable-tests --only-dependencies" + sh "cabal build all --only-dependencies" + sourcehutRun "build" job clonePath $ + sh "cabal build all" + sourcehutRun "test" job clonePath $ + sh "cabal test all --enable-tests" + sourcehutRun "haddock" job clonePath $ + sh "cabal haddock all" + sourcehutRun "sdist" job clonePath $ do + sh "cabal sdist -o ." + sh "mv ./*-*.tar.gz ../sdist.tar.gz" getEmails :: Project URI Void Package -> [String] getEmails = fmap (C.fromShortText . C.maintainer . C.packageDescription . pkgGpd) . prjPackages -sourcehutRun :: String -> ShM () -> ListBuilder (Either HsCiError SourcehutTask) () -sourcehutRun name shm = item $ do - shs <- runSh shm - return $ SourcehutTask name shs +sourcehutRun :: String -> CompilerVersion -> FilePath -> ShM () -> ListBuilder (Either HsCiError SourcehutTask) () +sourcehutRun name job clonePath shm = item $ do + shs <- runSh $ do + -- 2164: -e is set by default + sh' [2164] $ "cd " ++ clonePath + shm + return $ SourcehutTask (ghcVersionTask <> "-" <> name) shs + where ghcVersionTask = (\c -> if c == '.' then '_' else c) <$> dispGhcVersionShort job tell_env' :: String -> String -> String -tell_env' k v = "echo " ++ show ("export" ++ k ++ "=" ++ v) ++ " >> \"~/.buildenv\"" +tell_env' k v = "echo " ++ show ("export " ++ k ++ "=" ++ v) ++ " >> ~/.buildenv" tell_env :: String -> String -> ShM () tell_env k v = sh $ tell_env' k v From df19edfc7eafacdc19906f2e3937e390ee24a593 Mon Sep 17 00:00:00 2001 From: Francesco Gazzetta Date: Wed, 10 Nov 2021 20:27:43 +0100 Subject: [PATCH 06/23] sourcehut: remove .git suffix from work dir --- src/HaskellCI/Sourcehut.hs | 8 +++++++- 1 file changed, 7 insertions(+), 1 deletion(-) diff --git a/src/HaskellCI/Sourcehut.hs b/src/HaskellCI/Sourcehut.hs index 26844db8..e45a3334 100644 --- a/src/HaskellCI/Sourcehut.hs +++ b/src/HaskellCI/Sourcehut.hs @@ -133,7 +133,7 @@ makeSourcehut argv config@Config{..} SourcehutOptions{..} prj JobVersions{linuxV , srhtManifestTriggers = SourcehutTriggerEmail <$> getEmails prj , srhtManifestEnvironment = mempty } - clonePath = takeFileName sourcehutOptSource + clonePath = removeSuffix ".git" $ takeFileName sourcehutOptSource -- MAYBE reader for job and clonePath mkTasksForGhc :: CompilerVersion -> Either HsCiError [SourcehutTask] mkTasksForGhc job = sequence $ buildList $ do @@ -154,6 +154,12 @@ makeSourcehut argv config@Config{..} SourcehutOptions{..} prj JobVersions{linuxV sh "cabal sdist -o ." sh "mv ./*-*.tar.gz ../sdist.tar.gz" +removeSuffix :: String -> String -> String +removeSuffix suffix orig = + fromMaybe orig $ stripSuffix suffix orig + where + stripSuffix sf str = reverse <$> stripPrefix (reverse sf) (reverse str) + getEmails :: Project URI Void Package -> [String] getEmails = fmap (C.fromShortText . C.maintainer . C.packageDescription . pkgGpd) . prjPackages From 5dda9b03333e461bdd7ae32f1c5337e5582fcc96 Mon Sep 17 00:00:00 2001 From: Francesco Gazzetta Date: Wed, 10 Nov 2021 20:28:25 +0100 Subject: [PATCH 07/23] sourcehut: remove useless sdist step --- src/HaskellCI/Sourcehut.hs | 5 +---- 1 file changed, 1 insertion(+), 4 deletions(-) diff --git a/src/HaskellCI/Sourcehut.hs b/src/HaskellCI/Sourcehut.hs index e45a3334..2ea172ce 100644 --- a/src/HaskellCI/Sourcehut.hs +++ b/src/HaskellCI/Sourcehut.hs @@ -127,7 +127,7 @@ makeSourcehut argv config@Config{..} SourcehutOptions{..} prj JobVersions{linuxV , srhtManifestRepositories = M.singleton "hvr-ghc" ("http://ppa.launchpad.net/hvr/ghc/ubuntu " ++ C.prettyShow cfgUbuntu ++ " main ff3aeacef6f88286") - , srhtManifestArtifacts = ["sdist.tar.gz"] -- TODO sdist (with proper name) and maybe the binary + , srhtManifestArtifacts = [] , srhtManifestSources = [sourcehutOptSource] , srhtManifestTasks = prepare : tasks , srhtManifestTriggers = SourcehutTriggerEmail <$> getEmails prj @@ -150,9 +150,6 @@ makeSourcehut argv config@Config{..} SourcehutOptions{..} prj JobVersions{linuxV sh "cabal test all --enable-tests" sourcehutRun "haddock" job clonePath $ sh "cabal haddock all" - sourcehutRun "sdist" job clonePath $ do - sh "cabal sdist -o ." - sh "mv ./*-*.tar.gz ../sdist.tar.gz" removeSuffix :: String -> String -> String removeSuffix suffix orig = From 7f79dae76b41878e640be5800f43f897baa58b11 Mon Sep 17 00:00:00 2001 From: Francesco Gazzetta Date: Wed, 10 Nov 2021 21:20:16 +0100 Subject: [PATCH 08/23] Remove RecordWildCards from HaskellCI.hs --- src/HaskellCI.hs | 7 +++---- 1 file changed, 3 insertions(+), 4 deletions(-) diff --git a/src/HaskellCI.hs b/src/HaskellCI.hs index 69ed6a9d..496cb8c5 100644 --- a/src/HaskellCI.hs +++ b/src/HaskellCI.hs @@ -2,7 +2,6 @@ {-# LANGUAGE MultiWayIf #-} {-# LANGUAGE NamedFieldPuns #-} {-# LANGUAGE OverloadedStrings #-} -{-# LANGUAGE RecordWildCards #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeApplications #-} @@ -435,7 +434,7 @@ genSourcehutFromConfigs -> Project URI Void Package -> Set CompilerVersion -> m (M.Map FilePath ByteString) -genSourcehutFromConfigs argv config gitconfig SourcehutOptions{..} prj vs = do +genSourcehutFromConfigs argv config gitconfig srhtOpts@SourcehutOptions{sourcehutOptSource} prj vs = do let jobVersions = makeJobVersions config vs gitRemote = case M.toList (gitCfgRemotes gitconfig) of [(_,url)] -> Just url @@ -449,8 +448,8 @@ genSourcehutFromConfigs argv config gitconfig SourcehutOptions{..} prj vs = do Nothing -> case gitRemote of Just url -> return $ TS.unpack url Nothing -> putStrLnErr "multiple/no remotes found and --sourcehut-source was not used" - let srhtOpts = SourcehutOptions{sourcehutOptSource = sourcehutOptSource',..} - case makeSourcehut argv config srhtOpts prj jobVersions of + let srhtOpts' = srhtOpts {sourcehutOptSource = sourcehutOptSource'} + case makeSourcehut argv config srhtOpts' prj jobVersions of Left err -> putStrLnErr $ displayException err Right sourcehut -> do describeJobs "Sourcehut config" (cfgTestedWith config) jobVersions (prjPackages prj) From 2a945795c9b7e362f919d5a979c61dbea269a053 Mon Sep 17 00:00:00 2001 From: Francesco Gazzetta Date: Sun, 21 Nov 2021 11:56:19 +0100 Subject: [PATCH 09/23] Sourcehut: fix warnings --- src/HaskellCI/Sourcehut.hs | 20 +------------------- src/HaskellCI/Sourcehut/Yaml.hs | 2 -- 2 files changed, 1 insertion(+), 21 deletions(-) diff --git a/src/HaskellCI/Sourcehut.hs b/src/HaskellCI/Sourcehut.hs index 2ea172ce..b9171bf0 100644 --- a/src/HaskellCI/Sourcehut.hs +++ b/src/HaskellCI/Sourcehut.hs @@ -10,39 +10,21 @@ module HaskellCI.Sourcehut ( import HaskellCI.Prelude -import Data.Bifunctor (first) import qualified Data.Map.Strict as M import qualified Data.Set as S -import qualified Distribution.Fields.Pretty as C -import qualified Distribution.Package as C import qualified Distribution.Pretty as C import qualified Distribution.Types.GenericPackageDescription as C import qualified Distribution.Types.PackageDescription as C -import qualified Distribution.Types.VersionRange as C import qualified Distribution.Utils.ShortText as C -import qualified Distribution.Version as C import System.FilePath.Posix (takeFileName) import Cabal.Project -import HaskellCI.Auxiliary import HaskellCI.Compiler import HaskellCI.Config -import HaskellCI.Config.ConstraintSet -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.Validity -import HaskellCI.HeadHackage import HaskellCI.Jobs import HaskellCI.List -import HaskellCI.MonadErr import HaskellCI.Package import HaskellCI.Sh -import HaskellCI.ShVersionRange -import HaskellCI.Tools import HaskellCI.Sourcehut.Yaml import HaskellCI.VersionInfo @@ -103,7 +85,7 @@ makeSourcehut -> Project URI Void Package -> JobVersions -> Either HsCiError Sourcehut -makeSourcehut argv config@Config{..} SourcehutOptions{..} prj JobVersions{linuxVersions} = +makeSourcehut _argv Config{..} SourcehutOptions{..} prj JobVersions{linuxVersions} = Sourcehut <$> if sourcehutOptParallel then parallelManifests diff --git a/src/HaskellCI/Sourcehut/Yaml.hs b/src/HaskellCI/Sourcehut/Yaml.hs index 93fdad20..17c70786 100644 --- a/src/HaskellCI/Sourcehut/Yaml.hs +++ b/src/HaskellCI/Sourcehut/Yaml.hs @@ -6,11 +6,9 @@ module HaskellCI.Sourcehut.Yaml where import HaskellCI.Prelude -import qualified Data.Aeson as Aeson import qualified Data.Map.Strict as M import HaskellCI.Config.Ubuntu -import HaskellCI.List import HaskellCI.Sh import HaskellCI.YamlSyntax From 95e6e33485a837d25b52364b8b3d83dddf6d0296 Mon Sep 17 00:00:00 2001 From: Francesco Gazzetta Date: Mon, 29 Nov 2021 16:59:03 +0100 Subject: [PATCH 10/23] sourcehut: --apt --- src/HaskellCI/Cli.hs | 6 +++++- src/HaskellCI/Sourcehut.hs | 9 ++++++--- 2 files changed, 11 insertions(+), 4 deletions(-) diff --git a/src/HaskellCI/Cli.hs b/src/HaskellCI/Cli.hs index b3c0e37a..5a70d7cf 100644 --- a/src/HaskellCI/Cli.hs +++ b/src/HaskellCI/Cli.hs @@ -154,7 +154,11 @@ cliParserInfo = O.info ((,) <$> cmdP <*> optionsP O.<**> versionP O.<**> O.helpe sourcehutP = fmap CommandSourcehut $ SourcehutOptions <$> O.strArgument (O.metavar "CABAL.FILE" <> O.action "file" <> O.help "Either or cabal.project") <*> optional (O.strOption (O.long "source" <> O.metavar "URI" <> O.help "The source to test (default: from git remote)")) - <*> O.switch (O.long "sourcehut-parallel" <> O.help "In Sourcehut, use many manifests to run jobs in parallel") + <*> O.switch (O.long "sourcehut-parallel" <> O.help ( + "In Sourcehut, use many manifests to run jobs in parallel. " <> + "Disabled by default because in the sr.ht instance a maximum of " <> + "4 parallel jobs are allowed." + )) ------------------------------------------------------------------------------- -- Parsing helpers diff --git a/src/HaskellCI/Sourcehut.hs b/src/HaskellCI/Sourcehut.hs index b9171bf0..c810e542 100644 --- a/src/HaskellCI/Sourcehut.hs +++ b/src/HaskellCI/Sourcehut.hs @@ -15,10 +15,12 @@ import qualified Data.Set as S import qualified Distribution.Pretty as C import qualified Distribution.Types.GenericPackageDescription as C import qualified Distribution.Types.PackageDescription as C +import qualified Distribution.Types.VersionRange as C import qualified Distribution.Utils.ShortText as C import System.FilePath.Posix (takeFileName) import Cabal.Project +import HaskellCI.Auxiliary import HaskellCI.Compiler import HaskellCI.Config import HaskellCI.Jobs @@ -85,7 +87,7 @@ makeSourcehut -> Project URI Void Package -> JobVersions -> Either HsCiError Sourcehut -makeSourcehut _argv Config{..} SourcehutOptions{..} prj JobVersions{linuxVersions} = +makeSourcehut _argv config@Config{..} SourcehutOptions{..} prj jobs@JobVersions{linuxVersions} = Sourcehut <$> if sourcehutOptParallel then parallelManifests @@ -105,7 +107,7 @@ makeSourcehut _argv Config{..} SourcehutOptions{..} prj JobVersions{linuxVersion tasks <- concat <$> traverse mkTasksForGhc (S.toList jobs) return SourcehutManifest { srhtManifestImage = cfgUbuntu - , srhtManifestPackages = "gcc" : "cabal-install-3.4" : (dispGhcVersion <$> S.toList jobs) + , srhtManifestPackages = ("gcc" : "cabal-install-3.4" : (dispGhcVersion <$> S.toList jobs)) ++ toList cfgApt , srhtManifestRepositories = M.singleton "hvr-ghc" ("http://ppa.launchpad.net/hvr/ghc/ubuntu " ++ C.prettyShow cfgUbuntu ++ " main ff3aeacef6f88286") @@ -130,8 +132,9 @@ makeSourcehut _argv Config{..} SourcehutOptions{..} prj JobVersions{linuxVersion sh "cabal build all" sourcehutRun "test" job clonePath $ sh "cabal test all --enable-tests" - sourcehutRun "haddock" job clonePath $ + when (hasLibrary && not (equivVersionRanges C.noVersion cfgHaddock)) $ sourcehutRun "haddock" job clonePath $ sh "cabal haddock all" + Auxiliary {..} = auxiliary config prj jobs removeSuffix :: String -> String -> String removeSuffix suffix orig = From 37ffdcf3d416e803f32dd8572a1398db41352469 Mon Sep 17 00:00:00 2001 From: Francesco Gazzetta Date: Mon, 29 Nov 2021 17:17:11 +0100 Subject: [PATCH 11/23] sourcehut: formatting --- src/HaskellCI/Sourcehut.hs | 19 ++++++++++++++----- 1 file changed, 14 insertions(+), 5 deletions(-) diff --git a/src/HaskellCI/Sourcehut.hs b/src/HaskellCI/Sourcehut.hs index c810e542..9ac96e54 100644 --- a/src/HaskellCI/Sourcehut.hs +++ b/src/HaskellCI/Sourcehut.hs @@ -87,27 +87,34 @@ makeSourcehut -> Project URI Void Package -> JobVersions -> Either HsCiError Sourcehut -makeSourcehut _argv config@Config{..} SourcehutOptions{..} prj jobs@JobVersions{linuxVersions} = +makeSourcehut _argv config@Config {..} SourcehutOptions {..} prj jobs@JobVersions {..} = Sourcehut <$> if sourcehutOptParallel then parallelManifests else M.singleton "all" <$> sequentialManifest where + Auxiliary {..} = auxiliary config prj jobs + parallelManifests :: Either HsCiError (M.Map String SourcehutManifest) parallelManifests = fmap (M.mapKeys dispGhcVersionShort) $ sequence $ M.fromSet (mkManifest . S.singleton) linuxVersions + sequentialManifest :: Either HsCiError SourcehutManifest sequentialManifest = mkManifest linuxVersions + mkManifest :: Set CompilerVersion -> Either HsCiError SourcehutManifest - mkManifest jobs = do + mkManifest compilers = do prepare <- fmap (SourcehutTask "all-prepare") $ runSh $ do sh "export PATH=$PATH:/opt/cabal/bin" tell_env "PATH" "$PATH:/opt/cabal/bin" sh "cabal update" - tasks <- concat <$> traverse mkTasksForGhc (S.toList jobs) + tasks <- concat <$> traverse mkTasksForGhc (S.toList compilers) return SourcehutManifest { srhtManifestImage = cfgUbuntu - , srhtManifestPackages = ("gcc" : "cabal-install-3.4" : (dispGhcVersion <$> S.toList jobs)) ++ toList cfgApt + , srhtManifestPackages = + toList cfgApt ++ + ( "gcc" : "cabal-install-3.4" : + (dispGhcVersion <$> S.toList compilers)) , srhtManifestRepositories = M.singleton "hvr-ghc" ("http://ppa.launchpad.net/hvr/ghc/ubuntu " ++ C.prettyShow cfgUbuntu ++ " main ff3aeacef6f88286") @@ -117,7 +124,10 @@ makeSourcehut _argv config@Config{..} SourcehutOptions{..} prj jobs@JobVersions{ , srhtManifestTriggers = SourcehutTriggerEmail <$> getEmails prj , srhtManifestEnvironment = mempty } + + clonePath :: FilePath clonePath = removeSuffix ".git" $ takeFileName sourcehutOptSource + -- MAYBE reader for job and clonePath mkTasksForGhc :: CompilerVersion -> Either HsCiError [SourcehutTask] mkTasksForGhc job = sequence $ buildList $ do @@ -134,7 +144,6 @@ makeSourcehut _argv config@Config{..} SourcehutOptions{..} prj jobs@JobVersions{ sh "cabal test all --enable-tests" when (hasLibrary && not (equivVersionRanges C.noVersion cfgHaddock)) $ sourcehutRun "haddock" job clonePath $ sh "cabal haddock all" - Auxiliary {..} = auxiliary config prj jobs removeSuffix :: String -> String -> String removeSuffix suffix orig = From 0f366610e5b55a9d2bba609e4568e0bb829eeafe Mon Sep 17 00:00:00 2001 From: Francesco Gazzetta Date: Mon, 29 Nov 2021 17:19:44 +0100 Subject: [PATCH 12/23] sourcehut: indentation --- src/HaskellCI/Sourcehut.hs | 90 +++++++++++++++++++------------------- 1 file changed, 45 insertions(+), 45 deletions(-) diff --git a/src/HaskellCI/Sourcehut.hs b/src/HaskellCI/Sourcehut.hs index 9ac96e54..8b583525 100644 --- a/src/HaskellCI/Sourcehut.hs +++ b/src/HaskellCI/Sourcehut.hs @@ -35,10 +35,10 @@ import HaskellCI.VersionInfo ------------------------------------------------------------------------------- data SourcehutOptions src = SourcehutOptions - { sourcehutOptPath :: FilePath - , sourcehutOptSource :: src - , sourcehutOptParallel :: Bool - } + { sourcehutOptPath :: FilePath + , sourcehutOptSource :: src + , sourcehutOptParallel :: Bool + } deriving Show ------------------------------------------------------------------------------- @@ -89,41 +89,41 @@ makeSourcehut -> Either HsCiError Sourcehut makeSourcehut _argv config@Config {..} SourcehutOptions {..} prj jobs@JobVersions {..} = Sourcehut <$> - if sourcehutOptParallel - then parallelManifests - else M.singleton "all" <$> sequentialManifest + if sourcehutOptParallel + then parallelManifests + else M.singleton "all" <$> sequentialManifest where Auxiliary {..} = auxiliary config prj jobs parallelManifests :: Either HsCiError (M.Map String SourcehutManifest) parallelManifests = fmap (M.mapKeys dispGhcVersionShort) $ - sequence $ M.fromSet (mkManifest . S.singleton) linuxVersions + sequence $ M.fromSet (mkManifest . S.singleton) linuxVersions sequentialManifest :: Either HsCiError SourcehutManifest sequentialManifest = mkManifest linuxVersions mkManifest :: Set CompilerVersion -> Either HsCiError SourcehutManifest mkManifest compilers = do - prepare <- fmap (SourcehutTask "all-prepare") $ runSh $ do - sh "export PATH=$PATH:/opt/cabal/bin" - tell_env "PATH" "$PATH:/opt/cabal/bin" - sh "cabal update" - tasks <- concat <$> traverse mkTasksForGhc (S.toList compilers) - return SourcehutManifest - { srhtManifestImage = cfgUbuntu - , srhtManifestPackages = - toList cfgApt ++ - ( "gcc" : "cabal-install-3.4" : - (dispGhcVersion <$> S.toList compilers)) - , srhtManifestRepositories = M.singleton - "hvr-ghc" - ("http://ppa.launchpad.net/hvr/ghc/ubuntu " ++ C.prettyShow cfgUbuntu ++ " main ff3aeacef6f88286") - , srhtManifestArtifacts = [] - , srhtManifestSources = [sourcehutOptSource] - , srhtManifestTasks = prepare : tasks - , srhtManifestTriggers = SourcehutTriggerEmail <$> getEmails prj - , srhtManifestEnvironment = mempty - } + prepare <- fmap (SourcehutTask "all-prepare") $ runSh $ do + sh "export PATH=$PATH:/opt/cabal/bin" + tell_env "PATH" "$PATH:/opt/cabal/bin" + sh "cabal update" + tasks <- concat <$> traverse mkTasksForGhc (S.toList compilers) + return SourcehutManifest + { srhtManifestImage = cfgUbuntu + , srhtManifestPackages = + toList cfgApt ++ + ( "gcc" : "cabal-install-3.4" : + (dispGhcVersion <$> S.toList compilers)) + , srhtManifestRepositories = M.singleton + "hvr-ghc" + ("http://ppa.launchpad.net/hvr/ghc/ubuntu " ++ C.prettyShow cfgUbuntu ++ " main ff3aeacef6f88286") + , srhtManifestArtifacts = [] + , srhtManifestSources = [sourcehutOptSource] + , srhtManifestTasks = prepare : tasks + , srhtManifestTriggers = SourcehutTriggerEmail <$> getEmails prj + , srhtManifestEnvironment = mempty + } clonePath :: FilePath clonePath = removeSuffix ".git" $ takeFileName sourcehutOptSource @@ -131,23 +131,23 @@ makeSourcehut _argv config@Config {..} SourcehutOptions {..} prj jobs@JobVersion -- MAYBE reader for job and clonePath mkTasksForGhc :: CompilerVersion -> Either HsCiError [SourcehutTask] mkTasksForGhc job = sequence $ buildList $ do - sourcehutRun "prepare" job clonePath $ - sh $ "cabal configure -w /opt/ghc/bin/" ++ dispGhcVersion job - sourcehutRun "check" job clonePath $ - sh "cabal check" - when cfgInstallDeps $ sourcehutRun "dependencies" job clonePath $ do - sh "cabal build all --enable-tests --only-dependencies" - sh "cabal build all --only-dependencies" - sourcehutRun "build" job clonePath $ - sh "cabal build all" - sourcehutRun "test" job clonePath $ - sh "cabal test all --enable-tests" - when (hasLibrary && not (equivVersionRanges C.noVersion cfgHaddock)) $ sourcehutRun "haddock" job clonePath $ - sh "cabal haddock all" + sourcehutRun "prepare" job clonePath $ + sh $ "cabal configure -w /opt/ghc/bin/" ++ dispGhcVersion job + sourcehutRun "check" job clonePath $ + sh "cabal check" + when cfgInstallDeps $ sourcehutRun "dependencies" job clonePath $ do + sh "cabal build all --enable-tests --only-dependencies" + sh "cabal build all --only-dependencies" + sourcehutRun "build" job clonePath $ + sh "cabal build all" + sourcehutRun "test" job clonePath $ + sh "cabal test all --enable-tests" + when (hasLibrary && not (equivVersionRanges C.noVersion cfgHaddock)) $ sourcehutRun "haddock" job clonePath $ + sh "cabal haddock all" removeSuffix :: String -> String -> String removeSuffix suffix orig = - fromMaybe orig $ stripSuffix suffix orig + fromMaybe orig $ stripSuffix suffix orig where stripSuffix sf str = reverse <$> stripPrefix (reverse sf) (reverse str) @@ -157,9 +157,9 @@ getEmails = fmap (C.fromShortText . C.maintainer . C.packageDescription . pkgGpd sourcehutRun :: String -> CompilerVersion -> FilePath -> ShM () -> ListBuilder (Either HsCiError SourcehutTask) () sourcehutRun name job clonePath shm = item $ do shs <- runSh $ do - -- 2164: -e is set by default - sh' [2164] $ "cd " ++ clonePath - shm + -- 2164: -e is set by default + sh' [2164] $ "cd " ++ clonePath + shm return $ SourcehutTask (ghcVersionTask <> "-" <> name) shs where ghcVersionTask = (\c -> if c == '.' then '_' else c) <$> dispGhcVersionShort job From 8aa44e3d45d0a5fe7dd850e0b375d07561a51be0 Mon Sep 17 00:00:00 2001 From: Francesco Gazzetta Date: Mon, 29 Nov 2021 18:09:13 +0100 Subject: [PATCH 13/23] sourcehut: deduplicate email triggers --- src/HaskellCI/Sourcehut.hs | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/src/HaskellCI/Sourcehut.hs b/src/HaskellCI/Sourcehut.hs index 8b583525..7bbae2c4 100644 --- a/src/HaskellCI/Sourcehut.hs +++ b/src/HaskellCI/Sourcehut.hs @@ -10,6 +10,7 @@ module HaskellCI.Sourcehut ( import HaskellCI.Prelude +import Data.Containers.ListUtils (nubOrd) import qualified Data.Map.Strict as M import qualified Data.Set as S import qualified Distribution.Pretty as C @@ -121,7 +122,7 @@ makeSourcehut _argv config@Config {..} SourcehutOptions {..} prj jobs@JobVersion , srhtManifestArtifacts = [] , srhtManifestSources = [sourcehutOptSource] , srhtManifestTasks = prepare : tasks - , srhtManifestTriggers = SourcehutTriggerEmail <$> getEmails prj + , srhtManifestTriggers = SourcehutTriggerEmail <$> nubOrd (getEmails prj) , srhtManifestEnvironment = mempty } From 31e506525e7126b8d11e9845352698ed49a03e3a Mon Sep 17 00:00:00 2001 From: Francesco Gazzetta Date: Mon, 29 Nov 2021 19:08:39 +0100 Subject: [PATCH 14/23] sourcehut: add golden tests --- fixtures/all-versions.sourcehut | 932 ++++++++ fixtures/all-versions.sourcehut-parallel | 2252 ++++++++++++++++++ fixtures/copy-fields-all.sourcehut | 652 +++++ fixtures/copy-fields-all.sourcehut-parallel | 1552 ++++++++++++ fixtures/copy-fields-none.sourcehut | 652 +++++ fixtures/copy-fields-none.sourcehut-parallel | 1552 ++++++++++++ fixtures/copy-fields-some.sourcehut | 652 +++++ fixtures/copy-fields-some.sourcehut-parallel | 1552 ++++++++++++ fixtures/empty-line.sourcehut | 672 ++++++ fixtures/empty-line.sourcehut-parallel | 1602 +++++++++++++ fixtures/enabled-jobs.sourcehut | 572 +++++ fixtures/enabled-jobs.sourcehut-parallel | 1352 +++++++++++ fixtures/fail-versions.sourcehut | 3 + fixtures/fail-versions.sourcehut-parallel | 3 + fixtures/irc-channels.sourcehut | 652 +++++ fixtures/irc-channels.sourcehut-parallel | 1552 ++++++++++++ fixtures/messy.sourcehut | 673 ++++++ fixtures/messy.sourcehut-parallel | 1634 +++++++++++++ fixtures/psql.sourcehut | 652 +++++ fixtures/psql.sourcehut-parallel | 1552 ++++++++++++ fixtures/travis-patch.sourcehut | 652 +++++ fixtures/travis-patch.sourcehut-parallel | 1552 ++++++++++++ haskell-ci.cabal | 1 + src/HaskellCI.hs | 1 + test/Tests.hs | 27 +- 25 files changed, 22942 insertions(+), 6 deletions(-) create mode 100644 fixtures/all-versions.sourcehut create mode 100644 fixtures/all-versions.sourcehut-parallel create mode 100644 fixtures/copy-fields-all.sourcehut create mode 100644 fixtures/copy-fields-all.sourcehut-parallel create mode 100644 fixtures/copy-fields-none.sourcehut create mode 100644 fixtures/copy-fields-none.sourcehut-parallel create mode 100644 fixtures/copy-fields-some.sourcehut create mode 100644 fixtures/copy-fields-some.sourcehut-parallel create mode 100644 fixtures/empty-line.sourcehut create mode 100644 fixtures/empty-line.sourcehut-parallel create mode 100644 fixtures/enabled-jobs.sourcehut create mode 100644 fixtures/enabled-jobs.sourcehut-parallel create mode 100644 fixtures/fail-versions.sourcehut create mode 100644 fixtures/fail-versions.sourcehut-parallel create mode 100644 fixtures/irc-channels.sourcehut create mode 100644 fixtures/irc-channels.sourcehut-parallel create mode 100644 fixtures/messy.sourcehut create mode 100644 fixtures/messy.sourcehut-parallel create mode 100644 fixtures/psql.sourcehut create mode 100644 fixtures/psql.sourcehut-parallel create mode 100644 fixtures/travis-patch.sourcehut create mode 100644 fixtures/travis-patch.sourcehut-parallel diff --git a/fixtures/all-versions.sourcehut b/fixtures/all-versions.sourcehut new file mode 100644 index 00000000..d4095ad2 --- /dev/null +++ b/fixtures/all-versions.sourcehut @@ -0,0 +1,932 @@ +# SUCCESS +# *INFO* Generating Sourcehut config for testing for GHC versions: 7.0.1 7.0.2 7.0.3 7.0.4 7.2.1 7.2.2 7.4.1 7.4.2 7.6.1 7.6.2 7.6.3 7.8.1 7.8.2 7.8.3 7.8.4 7.10.1 7.10.2 7.10.3 8.0.1 8.0.2 8.2.1 8.2.2 8.4.1 8.4.2 8.4.3 8.4.4 8.6.1 8.6.2 8.6.3 8.6.4 8.6.5 8.8.1 8.8.2 8.8.3 8.8.4 8.10.1 8.10.2 8.10.3 8.10.4 8.10.5 8.10.6 8.10.7 9.0.1 9.2.1 ghcjs-8.4 +# manifest name: all +# This Sourcehut job script has been generated by a script via +# +# haskell-ci 'sourcehut' 'all-versions.project' +# +# 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 +# +# REGENDATA ["sourcehut","all-versions.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-7.0.1 + - ghc-7.0.2 + - ghc-7.0.3 + - ghc-7.0.4 + - ghc-7.2.1 + - ghc-7.2.2 + - ghc-7.4.1 + - ghc-7.4.2 + - ghc-7.6.1 + - ghc-7.6.2 + - ghc-7.6.3 + - ghc-7.8.1 + - ghc-7.8.2 + - ghc-7.8.3 + - ghc-7.8.4 + - ghc-7.10.1 + - ghc-7.10.2 + - ghc-7.10.3 + - ghc-8.0.1 + - ghc-8.0.2 + - ghc-8.2.1 + - ghc-8.2.2 + - ghc-8.4.1 + - ghc-8.4.2 + - ghc-8.4.3 + - ghc-8.4.4 + - ghc-8.6.1 + - ghc-8.6.2 + - ghc-8.6.3 + - ghc-8.6.4 + - ghc-8.6.5 + - ghc-8.8.1 + - ghc-8.8.2 + - ghc-8.8.3 + - ghc-8.8.4 + - ghc-8.10.1 + - ghc-8.10.2 + - ghc-8.10.3 + - ghc-8.10.4 + - ghc-8.10.5 + - ghc-8.10.6 + - ghc-8.10.7 + - ghc-9.0.1 + - ghc-9.2.1 + - ghcjs-8.4 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 7_0_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.0.1 + - 7_0_1-check: | + cd example.org + cabal check + - 7_0_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_0_1-build: | + cd example.org + cabal build all + - 7_0_1-test: | + cd example.org + cabal test all --enable-tests + - 7_0_1-haddock: | + cd example.org + cabal haddock all + - 7_0_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.0.2 + - 7_0_2-check: | + cd example.org + cabal check + - 7_0_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_0_2-build: | + cd example.org + cabal build all + - 7_0_2-test: | + cd example.org + cabal test all --enable-tests + - 7_0_2-haddock: | + cd example.org + cabal haddock all + - 7_0_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.0.3 + - 7_0_3-check: | + cd example.org + cabal check + - 7_0_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_0_3-build: | + cd example.org + cabal build all + - 7_0_3-test: | + cd example.org + cabal test all --enable-tests + - 7_0_3-haddock: | + cd example.org + cabal haddock all + - 7_0_4-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.0.4 + - 7_0_4-check: | + cd example.org + cabal check + - 7_0_4-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_0_4-build: | + cd example.org + cabal build all + - 7_0_4-test: | + cd example.org + cabal test all --enable-tests + - 7_0_4-haddock: | + cd example.org + cabal haddock all + - 7_2_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.2.1 + - 7_2_1-check: | + cd example.org + cabal check + - 7_2_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_2_1-build: | + cd example.org + cabal build all + - 7_2_1-test: | + cd example.org + cabal test all --enable-tests + - 7_2_1-haddock: | + cd example.org + cabal haddock all + - 7_2_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.2.2 + - 7_2_2-check: | + cd example.org + cabal check + - 7_2_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_2_2-build: | + cd example.org + cabal build all + - 7_2_2-test: | + cd example.org + cabal test all --enable-tests + - 7_2_2-haddock: | + cd example.org + cabal haddock all + - 7_4_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.4.1 + - 7_4_1-check: | + cd example.org + cabal check + - 7_4_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_4_1-build: | + cd example.org + cabal build all + - 7_4_1-test: | + cd example.org + cabal test all --enable-tests + - 7_4_1-haddock: | + cd example.org + cabal haddock all + - 7_4_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.4.2 + - 7_4_2-check: | + cd example.org + cabal check + - 7_4_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_4_2-build: | + cd example.org + cabal build all + - 7_4_2-test: | + cd example.org + cabal test all --enable-tests + - 7_4_2-haddock: | + cd example.org + cabal haddock all + - 7_6_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.6.1 + - 7_6_1-check: | + cd example.org + cabal check + - 7_6_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_6_1-build: | + cd example.org + cabal build all + - 7_6_1-test: | + cd example.org + cabal test all --enable-tests + - 7_6_1-haddock: | + cd example.org + cabal haddock all + - 7_6_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.6.2 + - 7_6_2-check: | + cd example.org + cabal check + - 7_6_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_6_2-build: | + cd example.org + cabal build all + - 7_6_2-test: | + cd example.org + cabal test all --enable-tests + - 7_6_2-haddock: | + cd example.org + cabal haddock all + - 7_6_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.6.3 + - 7_6_3-check: | + cd example.org + cabal check + - 7_6_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_6_3-build: | + cd example.org + cabal build all + - 7_6_3-test: | + cd example.org + cabal test all --enable-tests + - 7_6_3-haddock: | + cd example.org + cabal haddock all + - 7_8_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.8.1 + - 7_8_1-check: | + cd example.org + cabal check + - 7_8_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_8_1-build: | + cd example.org + cabal build all + - 7_8_1-test: | + cd example.org + cabal test all --enable-tests + - 7_8_1-haddock: | + cd example.org + cabal haddock all + - 7_8_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.8.2 + - 7_8_2-check: | + cd example.org + cabal check + - 7_8_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_8_2-build: | + cd example.org + cabal build all + - 7_8_2-test: | + cd example.org + cabal test all --enable-tests + - 7_8_2-haddock: | + cd example.org + cabal haddock all + - 7_8_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.8.3 + - 7_8_3-check: | + cd example.org + cabal check + - 7_8_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_8_3-build: | + cd example.org + cabal build all + - 7_8_3-test: | + cd example.org + cabal test all --enable-tests + - 7_8_3-haddock: | + cd example.org + cabal haddock all + - 7_8_4-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.8.4 + - 7_8_4-check: | + cd example.org + cabal check + - 7_8_4-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_8_4-build: | + cd example.org + cabal build all + - 7_8_4-test: | + cd example.org + cabal test all --enable-tests + - 7_8_4-haddock: | + cd example.org + cabal haddock all + - 7_10_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.10.1 + - 7_10_1-check: | + cd example.org + cabal check + - 7_10_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_10_1-build: | + cd example.org + cabal build all + - 7_10_1-test: | + cd example.org + cabal test all --enable-tests + - 7_10_1-haddock: | + cd example.org + cabal haddock all + - 7_10_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.10.2 + - 7_10_2-check: | + cd example.org + cabal check + - 7_10_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_10_2-build: | + cd example.org + cabal build all + - 7_10_2-test: | + cd example.org + cabal test all --enable-tests + - 7_10_2-haddock: | + cd example.org + cabal haddock all + - 7_10_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.10.3 + - 7_10_3-check: | + cd example.org + cabal check + - 7_10_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_10_3-build: | + cd example.org + cabal build all + - 7_10_3-test: | + cd example.org + cabal test all --enable-tests + - 7_10_3-haddock: | + cd example.org + cabal haddock all + - 8_0_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.0.1 + - 8_0_1-check: | + cd example.org + cabal check + - 8_0_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_0_1-build: | + cd example.org + cabal build all + - 8_0_1-test: | + cd example.org + cabal test all --enable-tests + - 8_0_1-haddock: | + cd example.org + cabal haddock all + - 8_0_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.0.2 + - 8_0_2-check: | + cd example.org + cabal check + - 8_0_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_0_2-build: | + cd example.org + cabal build all + - 8_0_2-test: | + cd example.org + cabal test all --enable-tests + - 8_0_2-haddock: | + cd example.org + cabal haddock all + - 8_2_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.2.1 + - 8_2_1-check: | + cd example.org + cabal check + - 8_2_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_2_1-build: | + cd example.org + cabal build all + - 8_2_1-test: | + cd example.org + cabal test all --enable-tests + - 8_2_1-haddock: | + cd example.org + cabal haddock all + - 8_2_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.2.2 + - 8_2_2-check: | + cd example.org + cabal check + - 8_2_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_2_2-build: | + cd example.org + cabal build all + - 8_2_2-test: | + cd example.org + cabal test all --enable-tests + - 8_2_2-haddock: | + cd example.org + cabal haddock all + - 8_4_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.4.1 + - 8_4_1-check: | + cd example.org + cabal check + - 8_4_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_4_1-build: | + cd example.org + cabal build all + - 8_4_1-test: | + cd example.org + cabal test all --enable-tests + - 8_4_1-haddock: | + cd example.org + cabal haddock all + - 8_4_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.4.2 + - 8_4_2-check: | + cd example.org + cabal check + - 8_4_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_4_2-build: | + cd example.org + cabal build all + - 8_4_2-test: | + cd example.org + cabal test all --enable-tests + - 8_4_2-haddock: | + cd example.org + cabal haddock all + - 8_4_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.4.3 + - 8_4_3-check: | + cd example.org + cabal check + - 8_4_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_4_3-build: | + cd example.org + cabal build all + - 8_4_3-test: | + cd example.org + cabal test all --enable-tests + - 8_4_3-haddock: | + cd example.org + cabal haddock all + - 8_4_4-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.4.4 + - 8_4_4-check: | + cd example.org + cabal check + - 8_4_4-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_4_4-build: | + cd example.org + cabal build all + - 8_4_4-test: | + cd example.org + cabal test all --enable-tests + - 8_4_4-haddock: | + cd example.org + cabal haddock all + - 8_6_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.6.1 + - 8_6_1-check: | + cd example.org + cabal check + - 8_6_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_6_1-build: | + cd example.org + cabal build all + - 8_6_1-test: | + cd example.org + cabal test all --enable-tests + - 8_6_1-haddock: | + cd example.org + cabal haddock all + - 8_6_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.6.2 + - 8_6_2-check: | + cd example.org + cabal check + - 8_6_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_6_2-build: | + cd example.org + cabal build all + - 8_6_2-test: | + cd example.org + cabal test all --enable-tests + - 8_6_2-haddock: | + cd example.org + cabal haddock all + - 8_6_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.6.3 + - 8_6_3-check: | + cd example.org + cabal check + - 8_6_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_6_3-build: | + cd example.org + cabal build all + - 8_6_3-test: | + cd example.org + cabal test all --enable-tests + - 8_6_3-haddock: | + cd example.org + cabal haddock all + - 8_6_4-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.6.4 + - 8_6_4-check: | + cd example.org + cabal check + - 8_6_4-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_6_4-build: | + cd example.org + cabal build all + - 8_6_4-test: | + cd example.org + cabal test all --enable-tests + - 8_6_4-haddock: | + cd example.org + cabal haddock all + - 8_6_5-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.6.5 + - 8_6_5-check: | + cd example.org + cabal check + - 8_6_5-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_6_5-build: | + cd example.org + cabal build all + - 8_6_5-test: | + cd example.org + cabal test all --enable-tests + - 8_6_5-haddock: | + cd example.org + cabal haddock all + - 8_8_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.8.1 + - 8_8_1-check: | + cd example.org + cabal check + - 8_8_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_8_1-build: | + cd example.org + cabal build all + - 8_8_1-test: | + cd example.org + cabal test all --enable-tests + - 8_8_1-haddock: | + cd example.org + cabal haddock all + - 8_8_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.8.2 + - 8_8_2-check: | + cd example.org + cabal check + - 8_8_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_8_2-build: | + cd example.org + cabal build all + - 8_8_2-test: | + cd example.org + cabal test all --enable-tests + - 8_8_2-haddock: | + cd example.org + cabal haddock all + - 8_8_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.8.3 + - 8_8_3-check: | + cd example.org + cabal check + - 8_8_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_8_3-build: | + cd example.org + cabal build all + - 8_8_3-test: | + cd example.org + cabal test all --enable-tests + - 8_8_3-haddock: | + cd example.org + cabal haddock all + - 8_8_4-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.8.4 + - 8_8_4-check: | + cd example.org + cabal check + - 8_8_4-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_8_4-build: | + cd example.org + cabal build all + - 8_8_4-test: | + cd example.org + cabal test all --enable-tests + - 8_8_4-haddock: | + cd example.org + cabal haddock all + - 8_10_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.1 + - 8_10_1-check: | + cd example.org + cabal check + - 8_10_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_1-build: | + cd example.org + cabal build all + - 8_10_1-test: | + cd example.org + cabal test all --enable-tests + - 8_10_1-haddock: | + cd example.org + cabal haddock all + - 8_10_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.2 + - 8_10_2-check: | + cd example.org + cabal check + - 8_10_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_2-build: | + cd example.org + cabal build all + - 8_10_2-test: | + cd example.org + cabal test all --enable-tests + - 8_10_2-haddock: | + cd example.org + cabal haddock all + - 8_10_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.3 + - 8_10_3-check: | + cd example.org + cabal check + - 8_10_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_3-build: | + cd example.org + cabal build all + - 8_10_3-test: | + cd example.org + cabal test all --enable-tests + - 8_10_3-haddock: | + cd example.org + cabal haddock all + - 8_10_4-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.4 + - 8_10_4-check: | + cd example.org + cabal check + - 8_10_4-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_4-build: | + cd example.org + cabal build all + - 8_10_4-test: | + cd example.org + cabal test all --enable-tests + - 8_10_4-haddock: | + cd example.org + cabal haddock all + - 8_10_5-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.5 + - 8_10_5-check: | + cd example.org + cabal check + - 8_10_5-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_5-build: | + cd example.org + cabal build all + - 8_10_5-test: | + cd example.org + cabal test all --enable-tests + - 8_10_5-haddock: | + cd example.org + cabal haddock all + - 8_10_6-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.6 + - 8_10_6-check: | + cd example.org + cabal check + - 8_10_6-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_6-build: | + cd example.org + cabal build all + - 8_10_6-test: | + cd example.org + cabal test all --enable-tests + - 8_10_6-haddock: | + cd example.org + cabal haddock all + - 8_10_7-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.7 + - 8_10_7-check: | + cd example.org + cabal check + - 8_10_7-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_7-build: | + cd example.org + cabal build all + - 8_10_7-test: | + cd example.org + cabal test all --enable-tests + - 8_10_7-haddock: | + cd example.org + cabal haddock all + - 9_0_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-9.0.1 + - 9_0_1-check: | + cd example.org + cabal check + - 9_0_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 9_0_1-build: | + cd example.org + cabal build all + - 9_0_1-test: | + cd example.org + cabal test all --enable-tests + - 9_0_1-haddock: | + cd example.org + cabal haddock all + - 9_2_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-9.2.1 + - 9_2_1-check: | + cd example.org + cabal check + - 9_2_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 9_2_1-build: | + cd example.org + cabal build all + - 9_2_1-test: | + cd example.org + cabal test all --enable-tests + - 9_2_1-haddock: | + cd example.org + cabal haddock all + - ghcjs-8_4-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghcjs-8.4 + - ghcjs-8_4-check: | + cd example.org + cabal check + - ghcjs-8_4-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - ghcjs-8_4-build: | + cd example.org + cabal build all + - ghcjs-8_4-test: | + cd example.org + cabal test all --enable-tests + - ghcjs-8_4-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: Oleg Grenrus diff --git a/fixtures/all-versions.sourcehut-parallel b/fixtures/all-versions.sourcehut-parallel new file mode 100644 index 00000000..57690f2a --- /dev/null +++ b/fixtures/all-versions.sourcehut-parallel @@ -0,0 +1,2252 @@ +# SUCCESS +# *INFO* Generating Sourcehut config for testing for GHC versions: 7.0.1 7.0.2 7.0.3 7.0.4 7.2.1 7.2.2 7.4.1 7.4.2 7.6.1 7.6.2 7.6.3 7.8.1 7.8.2 7.8.3 7.8.4 7.10.1 7.10.2 7.10.3 8.0.1 8.0.2 8.2.1 8.2.2 8.4.1 8.4.2 8.4.3 8.4.4 8.6.1 8.6.2 8.6.3 8.6.4 8.6.5 8.8.1 8.8.2 8.8.3 8.8.4 8.10.1 8.10.2 8.10.3 8.10.4 8.10.5 8.10.6 8.10.7 9.0.1 9.2.1 ghcjs-8.4 +# manifest name: 7.0.1 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci 'sourcehut' 'all-versions.project' +# +# 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 +# +# REGENDATA ["sourcehut","all-versions.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-7.0.1 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 7_0_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.0.1 + - 7_0_1-check: | + cd example.org + cabal check + - 7_0_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_0_1-build: | + cd example.org + cabal build all + - 7_0_1-test: | + cd example.org + cabal test all --enable-tests + - 7_0_1-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: Oleg Grenrus +# manifest name: 7.0.2 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci 'sourcehut' 'all-versions.project' +# +# 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 +# +# REGENDATA ["sourcehut","all-versions.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-7.0.2 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 7_0_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.0.2 + - 7_0_2-check: | + cd example.org + cabal check + - 7_0_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_0_2-build: | + cd example.org + cabal build all + - 7_0_2-test: | + cd example.org + cabal test all --enable-tests + - 7_0_2-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: Oleg Grenrus +# manifest name: 7.0.3 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci 'sourcehut' 'all-versions.project' +# +# 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 +# +# REGENDATA ["sourcehut","all-versions.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-7.0.3 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 7_0_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.0.3 + - 7_0_3-check: | + cd example.org + cabal check + - 7_0_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_0_3-build: | + cd example.org + cabal build all + - 7_0_3-test: | + cd example.org + cabal test all --enable-tests + - 7_0_3-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: Oleg Grenrus +# manifest name: 7.0.4 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci 'sourcehut' 'all-versions.project' +# +# 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 +# +# REGENDATA ["sourcehut","all-versions.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-7.0.4 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 7_0_4-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.0.4 + - 7_0_4-check: | + cd example.org + cabal check + - 7_0_4-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_0_4-build: | + cd example.org + cabal build all + - 7_0_4-test: | + cd example.org + cabal test all --enable-tests + - 7_0_4-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: Oleg Grenrus +# manifest name: 7.10.1 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci 'sourcehut' 'all-versions.project' +# +# 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 +# +# REGENDATA ["sourcehut","all-versions.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-7.10.1 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 7_10_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.10.1 + - 7_10_1-check: | + cd example.org + cabal check + - 7_10_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_10_1-build: | + cd example.org + cabal build all + - 7_10_1-test: | + cd example.org + cabal test all --enable-tests + - 7_10_1-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: Oleg Grenrus +# manifest name: 7.10.2 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci 'sourcehut' 'all-versions.project' +# +# 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 +# +# REGENDATA ["sourcehut","all-versions.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-7.10.2 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 7_10_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.10.2 + - 7_10_2-check: | + cd example.org + cabal check + - 7_10_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_10_2-build: | + cd example.org + cabal build all + - 7_10_2-test: | + cd example.org + cabal test all --enable-tests + - 7_10_2-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: Oleg Grenrus +# manifest name: 7.10.3 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci 'sourcehut' 'all-versions.project' +# +# 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 +# +# REGENDATA ["sourcehut","all-versions.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-7.10.3 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 7_10_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.10.3 + - 7_10_3-check: | + cd example.org + cabal check + - 7_10_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_10_3-build: | + cd example.org + cabal build all + - 7_10_3-test: | + cd example.org + cabal test all --enable-tests + - 7_10_3-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: Oleg Grenrus +# manifest name: 7.2.1 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci 'sourcehut' 'all-versions.project' +# +# 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 +# +# REGENDATA ["sourcehut","all-versions.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-7.2.1 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 7_2_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.2.1 + - 7_2_1-check: | + cd example.org + cabal check + - 7_2_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_2_1-build: | + cd example.org + cabal build all + - 7_2_1-test: | + cd example.org + cabal test all --enable-tests + - 7_2_1-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: Oleg Grenrus +# manifest name: 7.2.2 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci 'sourcehut' 'all-versions.project' +# +# 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 +# +# REGENDATA ["sourcehut","all-versions.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-7.2.2 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 7_2_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.2.2 + - 7_2_2-check: | + cd example.org + cabal check + - 7_2_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_2_2-build: | + cd example.org + cabal build all + - 7_2_2-test: | + cd example.org + cabal test all --enable-tests + - 7_2_2-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: Oleg Grenrus +# manifest name: 7.4.1 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci 'sourcehut' 'all-versions.project' +# +# 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 +# +# REGENDATA ["sourcehut","all-versions.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-7.4.1 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 7_4_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.4.1 + - 7_4_1-check: | + cd example.org + cabal check + - 7_4_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_4_1-build: | + cd example.org + cabal build all + - 7_4_1-test: | + cd example.org + cabal test all --enable-tests + - 7_4_1-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: Oleg Grenrus +# manifest name: 7.4.2 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci 'sourcehut' 'all-versions.project' +# +# 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 +# +# REGENDATA ["sourcehut","all-versions.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-7.4.2 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 7_4_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.4.2 + - 7_4_2-check: | + cd example.org + cabal check + - 7_4_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_4_2-build: | + cd example.org + cabal build all + - 7_4_2-test: | + cd example.org + cabal test all --enable-tests + - 7_4_2-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: Oleg Grenrus +# manifest name: 7.6.1 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci 'sourcehut' 'all-versions.project' +# +# 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 +# +# REGENDATA ["sourcehut","all-versions.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-7.6.1 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 7_6_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.6.1 + - 7_6_1-check: | + cd example.org + cabal check + - 7_6_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_6_1-build: | + cd example.org + cabal build all + - 7_6_1-test: | + cd example.org + cabal test all --enable-tests + - 7_6_1-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: Oleg Grenrus +# manifest name: 7.6.2 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci 'sourcehut' 'all-versions.project' +# +# 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 +# +# REGENDATA ["sourcehut","all-versions.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-7.6.2 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 7_6_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.6.2 + - 7_6_2-check: | + cd example.org + cabal check + - 7_6_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_6_2-build: | + cd example.org + cabal build all + - 7_6_2-test: | + cd example.org + cabal test all --enable-tests + - 7_6_2-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: Oleg Grenrus +# manifest name: 7.6.3 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci 'sourcehut' 'all-versions.project' +# +# 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 +# +# REGENDATA ["sourcehut","all-versions.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-7.6.3 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 7_6_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.6.3 + - 7_6_3-check: | + cd example.org + cabal check + - 7_6_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_6_3-build: | + cd example.org + cabal build all + - 7_6_3-test: | + cd example.org + cabal test all --enable-tests + - 7_6_3-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: Oleg Grenrus +# manifest name: 7.8.1 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci 'sourcehut' 'all-versions.project' +# +# 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 +# +# REGENDATA ["sourcehut","all-versions.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-7.8.1 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 7_8_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.8.1 + - 7_8_1-check: | + cd example.org + cabal check + - 7_8_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_8_1-build: | + cd example.org + cabal build all + - 7_8_1-test: | + cd example.org + cabal test all --enable-tests + - 7_8_1-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: Oleg Grenrus +# manifest name: 7.8.2 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci 'sourcehut' 'all-versions.project' +# +# 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 +# +# REGENDATA ["sourcehut","all-versions.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-7.8.2 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 7_8_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.8.2 + - 7_8_2-check: | + cd example.org + cabal check + - 7_8_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_8_2-build: | + cd example.org + cabal build all + - 7_8_2-test: | + cd example.org + cabal test all --enable-tests + - 7_8_2-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: Oleg Grenrus +# manifest name: 7.8.3 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci 'sourcehut' 'all-versions.project' +# +# 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 +# +# REGENDATA ["sourcehut","all-versions.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-7.8.3 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 7_8_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.8.3 + - 7_8_3-check: | + cd example.org + cabal check + - 7_8_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_8_3-build: | + cd example.org + cabal build all + - 7_8_3-test: | + cd example.org + cabal test all --enable-tests + - 7_8_3-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: Oleg Grenrus +# manifest name: 7.8.4 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci 'sourcehut' 'all-versions.project' +# +# 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 +# +# REGENDATA ["sourcehut","all-versions.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-7.8.4 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 7_8_4-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.8.4 + - 7_8_4-check: | + cd example.org + cabal check + - 7_8_4-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_8_4-build: | + cd example.org + cabal build all + - 7_8_4-test: | + cd example.org + cabal test all --enable-tests + - 7_8_4-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: Oleg Grenrus +# manifest name: 8.0.1 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci 'sourcehut' 'all-versions.project' +# +# 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 +# +# REGENDATA ["sourcehut","all-versions.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.0.1 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_0_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.0.1 + - 8_0_1-check: | + cd example.org + cabal check + - 8_0_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_0_1-build: | + cd example.org + cabal build all + - 8_0_1-test: | + cd example.org + cabal test all --enable-tests + - 8_0_1-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: Oleg Grenrus +# manifest name: 8.0.2 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci 'sourcehut' 'all-versions.project' +# +# 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 +# +# REGENDATA ["sourcehut","all-versions.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.0.2 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_0_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.0.2 + - 8_0_2-check: | + cd example.org + cabal check + - 8_0_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_0_2-build: | + cd example.org + cabal build all + - 8_0_2-test: | + cd example.org + cabal test all --enable-tests + - 8_0_2-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: Oleg Grenrus +# manifest name: 8.10.1 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci 'sourcehut' 'all-versions.project' +# +# 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 +# +# REGENDATA ["sourcehut","all-versions.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.10.1 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_10_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.1 + - 8_10_1-check: | + cd example.org + cabal check + - 8_10_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_1-build: | + cd example.org + cabal build all + - 8_10_1-test: | + cd example.org + cabal test all --enable-tests + - 8_10_1-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: Oleg Grenrus +# manifest name: 8.10.2 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci 'sourcehut' 'all-versions.project' +# +# 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 +# +# REGENDATA ["sourcehut","all-versions.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.10.2 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_10_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.2 + - 8_10_2-check: | + cd example.org + cabal check + - 8_10_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_2-build: | + cd example.org + cabal build all + - 8_10_2-test: | + cd example.org + cabal test all --enable-tests + - 8_10_2-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: Oleg Grenrus +# manifest name: 8.10.3 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci 'sourcehut' 'all-versions.project' +# +# 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 +# +# REGENDATA ["sourcehut","all-versions.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.10.3 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_10_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.3 + - 8_10_3-check: | + cd example.org + cabal check + - 8_10_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_3-build: | + cd example.org + cabal build all + - 8_10_3-test: | + cd example.org + cabal test all --enable-tests + - 8_10_3-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: Oleg Grenrus +# manifest name: 8.10.4 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci 'sourcehut' 'all-versions.project' +# +# 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 +# +# REGENDATA ["sourcehut","all-versions.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.10.4 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_10_4-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.4 + - 8_10_4-check: | + cd example.org + cabal check + - 8_10_4-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_4-build: | + cd example.org + cabal build all + - 8_10_4-test: | + cd example.org + cabal test all --enable-tests + - 8_10_4-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: Oleg Grenrus +# manifest name: 8.10.5 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci 'sourcehut' 'all-versions.project' +# +# 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 +# +# REGENDATA ["sourcehut","all-versions.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.10.5 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_10_5-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.5 + - 8_10_5-check: | + cd example.org + cabal check + - 8_10_5-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_5-build: | + cd example.org + cabal build all + - 8_10_5-test: | + cd example.org + cabal test all --enable-tests + - 8_10_5-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: Oleg Grenrus +# manifest name: 8.10.6 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci 'sourcehut' 'all-versions.project' +# +# 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 +# +# REGENDATA ["sourcehut","all-versions.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.10.6 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_10_6-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.6 + - 8_10_6-check: | + cd example.org + cabal check + - 8_10_6-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_6-build: | + cd example.org + cabal build all + - 8_10_6-test: | + cd example.org + cabal test all --enable-tests + - 8_10_6-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: Oleg Grenrus +# manifest name: 8.10.7 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci 'sourcehut' 'all-versions.project' +# +# 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 +# +# REGENDATA ["sourcehut","all-versions.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.10.7 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_10_7-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.7 + - 8_10_7-check: | + cd example.org + cabal check + - 8_10_7-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_7-build: | + cd example.org + cabal build all + - 8_10_7-test: | + cd example.org + cabal test all --enable-tests + - 8_10_7-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: Oleg Grenrus +# manifest name: 8.2.1 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci 'sourcehut' 'all-versions.project' +# +# 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 +# +# REGENDATA ["sourcehut","all-versions.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.2.1 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_2_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.2.1 + - 8_2_1-check: | + cd example.org + cabal check + - 8_2_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_2_1-build: | + cd example.org + cabal build all + - 8_2_1-test: | + cd example.org + cabal test all --enable-tests + - 8_2_1-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: Oleg Grenrus +# manifest name: 8.2.2 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci 'sourcehut' 'all-versions.project' +# +# 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 +# +# REGENDATA ["sourcehut","all-versions.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.2.2 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_2_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.2.2 + - 8_2_2-check: | + cd example.org + cabal check + - 8_2_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_2_2-build: | + cd example.org + cabal build all + - 8_2_2-test: | + cd example.org + cabal test all --enable-tests + - 8_2_2-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: Oleg Grenrus +# manifest name: 8.4.1 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci 'sourcehut' 'all-versions.project' +# +# 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 +# +# REGENDATA ["sourcehut","all-versions.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.4.1 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_4_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.4.1 + - 8_4_1-check: | + cd example.org + cabal check + - 8_4_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_4_1-build: | + cd example.org + cabal build all + - 8_4_1-test: | + cd example.org + cabal test all --enable-tests + - 8_4_1-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: Oleg Grenrus +# manifest name: 8.4.2 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci 'sourcehut' 'all-versions.project' +# +# 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 +# +# REGENDATA ["sourcehut","all-versions.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.4.2 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_4_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.4.2 + - 8_4_2-check: | + cd example.org + cabal check + - 8_4_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_4_2-build: | + cd example.org + cabal build all + - 8_4_2-test: | + cd example.org + cabal test all --enable-tests + - 8_4_2-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: Oleg Grenrus +# manifest name: 8.4.3 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci 'sourcehut' 'all-versions.project' +# +# 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 +# +# REGENDATA ["sourcehut","all-versions.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.4.3 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_4_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.4.3 + - 8_4_3-check: | + cd example.org + cabal check + - 8_4_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_4_3-build: | + cd example.org + cabal build all + - 8_4_3-test: | + cd example.org + cabal test all --enable-tests + - 8_4_3-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: Oleg Grenrus +# manifest name: 8.4.4 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci 'sourcehut' 'all-versions.project' +# +# 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 +# +# REGENDATA ["sourcehut","all-versions.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.4.4 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_4_4-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.4.4 + - 8_4_4-check: | + cd example.org + cabal check + - 8_4_4-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_4_4-build: | + cd example.org + cabal build all + - 8_4_4-test: | + cd example.org + cabal test all --enable-tests + - 8_4_4-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: Oleg Grenrus +# manifest name: 8.6.1 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci 'sourcehut' 'all-versions.project' +# +# 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 +# +# REGENDATA ["sourcehut","all-versions.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.6.1 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_6_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.6.1 + - 8_6_1-check: | + cd example.org + cabal check + - 8_6_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_6_1-build: | + cd example.org + cabal build all + - 8_6_1-test: | + cd example.org + cabal test all --enable-tests + - 8_6_1-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: Oleg Grenrus +# manifest name: 8.6.2 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci 'sourcehut' 'all-versions.project' +# +# 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 +# +# REGENDATA ["sourcehut","all-versions.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.6.2 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_6_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.6.2 + - 8_6_2-check: | + cd example.org + cabal check + - 8_6_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_6_2-build: | + cd example.org + cabal build all + - 8_6_2-test: | + cd example.org + cabal test all --enable-tests + - 8_6_2-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: Oleg Grenrus +# manifest name: 8.6.3 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci 'sourcehut' 'all-versions.project' +# +# 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 +# +# REGENDATA ["sourcehut","all-versions.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.6.3 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_6_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.6.3 + - 8_6_3-check: | + cd example.org + cabal check + - 8_6_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_6_3-build: | + cd example.org + cabal build all + - 8_6_3-test: | + cd example.org + cabal test all --enable-tests + - 8_6_3-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: Oleg Grenrus +# manifest name: 8.6.4 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci 'sourcehut' 'all-versions.project' +# +# 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 +# +# REGENDATA ["sourcehut","all-versions.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.6.4 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_6_4-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.6.4 + - 8_6_4-check: | + cd example.org + cabal check + - 8_6_4-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_6_4-build: | + cd example.org + cabal build all + - 8_6_4-test: | + cd example.org + cabal test all --enable-tests + - 8_6_4-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: Oleg Grenrus +# manifest name: 8.6.5 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci 'sourcehut' 'all-versions.project' +# +# 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 +# +# REGENDATA ["sourcehut","all-versions.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.6.5 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_6_5-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.6.5 + - 8_6_5-check: | + cd example.org + cabal check + - 8_6_5-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_6_5-build: | + cd example.org + cabal build all + - 8_6_5-test: | + cd example.org + cabal test all --enable-tests + - 8_6_5-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: Oleg Grenrus +# manifest name: 8.8.1 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci 'sourcehut' 'all-versions.project' +# +# 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 +# +# REGENDATA ["sourcehut","all-versions.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.8.1 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_8_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.8.1 + - 8_8_1-check: | + cd example.org + cabal check + - 8_8_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_8_1-build: | + cd example.org + cabal build all + - 8_8_1-test: | + cd example.org + cabal test all --enable-tests + - 8_8_1-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: Oleg Grenrus +# manifest name: 8.8.2 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci 'sourcehut' 'all-versions.project' +# +# 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 +# +# REGENDATA ["sourcehut","all-versions.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.8.2 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_8_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.8.2 + - 8_8_2-check: | + cd example.org + cabal check + - 8_8_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_8_2-build: | + cd example.org + cabal build all + - 8_8_2-test: | + cd example.org + cabal test all --enable-tests + - 8_8_2-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: Oleg Grenrus +# manifest name: 8.8.3 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci 'sourcehut' 'all-versions.project' +# +# 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 +# +# REGENDATA ["sourcehut","all-versions.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.8.3 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_8_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.8.3 + - 8_8_3-check: | + cd example.org + cabal check + - 8_8_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_8_3-build: | + cd example.org + cabal build all + - 8_8_3-test: | + cd example.org + cabal test all --enable-tests + - 8_8_3-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: Oleg Grenrus +# manifest name: 8.8.4 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci 'sourcehut' 'all-versions.project' +# +# 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 +# +# REGENDATA ["sourcehut","all-versions.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.8.4 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_8_4-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.8.4 + - 8_8_4-check: | + cd example.org + cabal check + - 8_8_4-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_8_4-build: | + cd example.org + cabal build all + - 8_8_4-test: | + cd example.org + cabal test all --enable-tests + - 8_8_4-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: Oleg Grenrus +# manifest name: 9.0.1 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci 'sourcehut' 'all-versions.project' +# +# 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 +# +# REGENDATA ["sourcehut","all-versions.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-9.0.1 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 9_0_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-9.0.1 + - 9_0_1-check: | + cd example.org + cabal check + - 9_0_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 9_0_1-build: | + cd example.org + cabal build all + - 9_0_1-test: | + cd example.org + cabal test all --enable-tests + - 9_0_1-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: Oleg Grenrus +# manifest name: 9.2.1 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci 'sourcehut' 'all-versions.project' +# +# 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 +# +# REGENDATA ["sourcehut","all-versions.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-9.2.1 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 9_2_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-9.2.1 + - 9_2_1-check: | + cd example.org + cabal check + - 9_2_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 9_2_1-build: | + cd example.org + cabal build all + - 9_2_1-test: | + cd example.org + cabal test all --enable-tests + - 9_2_1-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: Oleg Grenrus +# manifest name: ghcjs-8.4 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci 'sourcehut' 'all-versions.project' +# +# 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 +# +# REGENDATA ["sourcehut","all-versions.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghcjs-8.4 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - ghcjs-8_4-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghcjs-8.4 + - ghcjs-8_4-check: | + cd example.org + cabal check + - ghcjs-8_4-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - ghcjs-8_4-build: | + cd example.org + cabal build all + - ghcjs-8_4-test: | + cd example.org + cabal test all --enable-tests + - ghcjs-8_4-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: Oleg Grenrus diff --git a/fixtures/copy-fields-all.sourcehut b/fixtures/copy-fields-all.sourcehut new file mode 100644 index 00000000..8f18703c --- /dev/null +++ b/fixtures/copy-fields-all.sourcehut @@ -0,0 +1,652 @@ +# SUCCESS +# *INFO* Generating Sourcehut config for testing for GHC versions: 7.8.1 7.8.2 7.8.3 7.8.4 7.10.1 7.10.2 7.10.3 8.0.1 8.0.2 8.2.1 8.2.2 8.4.1 8.4.2 8.4.3 8.4.4 8.6.1 8.6.2 8.6.3 8.6.4 8.6.5 8.8.1 8.8.2 8.8.3 8.8.4 8.10.1 8.10.2 8.10.3 8.10.4 8.10.5 8.10.6 8.10.7 +# manifest name: all +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--copy-fields=all' 'sourcehut' 'copy-fields-all.project' +# +# 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 +# +# REGENDATA ["--copy-fields=all","sourcehut","copy-fields-all.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-7.8.1 + - ghc-7.8.2 + - ghc-7.8.3 + - ghc-7.8.4 + - ghc-7.10.1 + - ghc-7.10.2 + - ghc-7.10.3 + - ghc-8.0.1 + - ghc-8.0.2 + - ghc-8.2.1 + - ghc-8.2.2 + - ghc-8.4.1 + - ghc-8.4.2 + - ghc-8.4.3 + - ghc-8.4.4 + - ghc-8.6.1 + - ghc-8.6.2 + - ghc-8.6.3 + - ghc-8.6.4 + - ghc-8.6.5 + - ghc-8.8.1 + - ghc-8.8.2 + - ghc-8.8.3 + - ghc-8.8.4 + - ghc-8.10.1 + - ghc-8.10.2 + - ghc-8.10.3 + - ghc-8.10.4 + - ghc-8.10.5 + - ghc-8.10.6 + - ghc-8.10.7 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 7_8_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.8.1 + - 7_8_1-check: | + cd example.org + cabal check + - 7_8_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_8_1-build: | + cd example.org + cabal build all + - 7_8_1-test: | + cd example.org + cabal test all --enable-tests + - 7_8_1-haddock: | + cd example.org + cabal haddock all + - 7_8_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.8.2 + - 7_8_2-check: | + cd example.org + cabal check + - 7_8_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_8_2-build: | + cd example.org + cabal build all + - 7_8_2-test: | + cd example.org + cabal test all --enable-tests + - 7_8_2-haddock: | + cd example.org + cabal haddock all + - 7_8_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.8.3 + - 7_8_3-check: | + cd example.org + cabal check + - 7_8_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_8_3-build: | + cd example.org + cabal build all + - 7_8_3-test: | + cd example.org + cabal test all --enable-tests + - 7_8_3-haddock: | + cd example.org + cabal haddock all + - 7_8_4-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.8.4 + - 7_8_4-check: | + cd example.org + cabal check + - 7_8_4-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_8_4-build: | + cd example.org + cabal build all + - 7_8_4-test: | + cd example.org + cabal test all --enable-tests + - 7_8_4-haddock: | + cd example.org + cabal haddock all + - 7_10_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.10.1 + - 7_10_1-check: | + cd example.org + cabal check + - 7_10_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_10_1-build: | + cd example.org + cabal build all + - 7_10_1-test: | + cd example.org + cabal test all --enable-tests + - 7_10_1-haddock: | + cd example.org + cabal haddock all + - 7_10_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.10.2 + - 7_10_2-check: | + cd example.org + cabal check + - 7_10_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_10_2-build: | + cd example.org + cabal build all + - 7_10_2-test: | + cd example.org + cabal test all --enable-tests + - 7_10_2-haddock: | + cd example.org + cabal haddock all + - 7_10_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.10.3 + - 7_10_3-check: | + cd example.org + cabal check + - 7_10_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_10_3-build: | + cd example.org + cabal build all + - 7_10_3-test: | + cd example.org + cabal test all --enable-tests + - 7_10_3-haddock: | + cd example.org + cabal haddock all + - 8_0_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.0.1 + - 8_0_1-check: | + cd example.org + cabal check + - 8_0_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_0_1-build: | + cd example.org + cabal build all + - 8_0_1-test: | + cd example.org + cabal test all --enable-tests + - 8_0_1-haddock: | + cd example.org + cabal haddock all + - 8_0_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.0.2 + - 8_0_2-check: | + cd example.org + cabal check + - 8_0_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_0_2-build: | + cd example.org + cabal build all + - 8_0_2-test: | + cd example.org + cabal test all --enable-tests + - 8_0_2-haddock: | + cd example.org + cabal haddock all + - 8_2_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.2.1 + - 8_2_1-check: | + cd example.org + cabal check + - 8_2_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_2_1-build: | + cd example.org + cabal build all + - 8_2_1-test: | + cd example.org + cabal test all --enable-tests + - 8_2_1-haddock: | + cd example.org + cabal haddock all + - 8_2_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.2.2 + - 8_2_2-check: | + cd example.org + cabal check + - 8_2_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_2_2-build: | + cd example.org + cabal build all + - 8_2_2-test: | + cd example.org + cabal test all --enable-tests + - 8_2_2-haddock: | + cd example.org + cabal haddock all + - 8_4_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.4.1 + - 8_4_1-check: | + cd example.org + cabal check + - 8_4_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_4_1-build: | + cd example.org + cabal build all + - 8_4_1-test: | + cd example.org + cabal test all --enable-tests + - 8_4_1-haddock: | + cd example.org + cabal haddock all + - 8_4_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.4.2 + - 8_4_2-check: | + cd example.org + cabal check + - 8_4_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_4_2-build: | + cd example.org + cabal build all + - 8_4_2-test: | + cd example.org + cabal test all --enable-tests + - 8_4_2-haddock: | + cd example.org + cabal haddock all + - 8_4_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.4.3 + - 8_4_3-check: | + cd example.org + cabal check + - 8_4_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_4_3-build: | + cd example.org + cabal build all + - 8_4_3-test: | + cd example.org + cabal test all --enable-tests + - 8_4_3-haddock: | + cd example.org + cabal haddock all + - 8_4_4-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.4.4 + - 8_4_4-check: | + cd example.org + cabal check + - 8_4_4-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_4_4-build: | + cd example.org + cabal build all + - 8_4_4-test: | + cd example.org + cabal test all --enable-tests + - 8_4_4-haddock: | + cd example.org + cabal haddock all + - 8_6_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.6.1 + - 8_6_1-check: | + cd example.org + cabal check + - 8_6_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_6_1-build: | + cd example.org + cabal build all + - 8_6_1-test: | + cd example.org + cabal test all --enable-tests + - 8_6_1-haddock: | + cd example.org + cabal haddock all + - 8_6_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.6.2 + - 8_6_2-check: | + cd example.org + cabal check + - 8_6_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_6_2-build: | + cd example.org + cabal build all + - 8_6_2-test: | + cd example.org + cabal test all --enable-tests + - 8_6_2-haddock: | + cd example.org + cabal haddock all + - 8_6_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.6.3 + - 8_6_3-check: | + cd example.org + cabal check + - 8_6_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_6_3-build: | + cd example.org + cabal build all + - 8_6_3-test: | + cd example.org + cabal test all --enable-tests + - 8_6_3-haddock: | + cd example.org + cabal haddock all + - 8_6_4-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.6.4 + - 8_6_4-check: | + cd example.org + cabal check + - 8_6_4-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_6_4-build: | + cd example.org + cabal build all + - 8_6_4-test: | + cd example.org + cabal test all --enable-tests + - 8_6_4-haddock: | + cd example.org + cabal haddock all + - 8_6_5-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.6.5 + - 8_6_5-check: | + cd example.org + cabal check + - 8_6_5-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_6_5-build: | + cd example.org + cabal build all + - 8_6_5-test: | + cd example.org + cabal test all --enable-tests + - 8_6_5-haddock: | + cd example.org + cabal haddock all + - 8_8_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.8.1 + - 8_8_1-check: | + cd example.org + cabal check + - 8_8_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_8_1-build: | + cd example.org + cabal build all + - 8_8_1-test: | + cd example.org + cabal test all --enable-tests + - 8_8_1-haddock: | + cd example.org + cabal haddock all + - 8_8_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.8.2 + - 8_8_2-check: | + cd example.org + cabal check + - 8_8_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_8_2-build: | + cd example.org + cabal build all + - 8_8_2-test: | + cd example.org + cabal test all --enable-tests + - 8_8_2-haddock: | + cd example.org + cabal haddock all + - 8_8_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.8.3 + - 8_8_3-check: | + cd example.org + cabal check + - 8_8_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_8_3-build: | + cd example.org + cabal build all + - 8_8_3-test: | + cd example.org + cabal test all --enable-tests + - 8_8_3-haddock: | + cd example.org + cabal haddock all + - 8_8_4-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.8.4 + - 8_8_4-check: | + cd example.org + cabal check + - 8_8_4-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_8_4-build: | + cd example.org + cabal build all + - 8_8_4-test: | + cd example.org + cabal test all --enable-tests + - 8_8_4-haddock: | + cd example.org + cabal haddock all + - 8_10_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.1 + - 8_10_1-check: | + cd example.org + cabal check + - 8_10_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_1-build: | + cd example.org + cabal build all + - 8_10_1-test: | + cd example.org + cabal test all --enable-tests + - 8_10_1-haddock: | + cd example.org + cabal haddock all + - 8_10_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.2 + - 8_10_2-check: | + cd example.org + cabal check + - 8_10_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_2-build: | + cd example.org + cabal build all + - 8_10_2-test: | + cd example.org + cabal test all --enable-tests + - 8_10_2-haddock: | + cd example.org + cabal haddock all + - 8_10_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.3 + - 8_10_3-check: | + cd example.org + cabal check + - 8_10_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_3-build: | + cd example.org + cabal build all + - 8_10_3-test: | + cd example.org + cabal test all --enable-tests + - 8_10_3-haddock: | + cd example.org + cabal haddock all + - 8_10_4-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.4 + - 8_10_4-check: | + cd example.org + cabal check + - 8_10_4-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_4-build: | + cd example.org + cabal build all + - 8_10_4-test: | + cd example.org + cabal test all --enable-tests + - 8_10_4-haddock: | + cd example.org + cabal haddock all + - 8_10_5-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.5 + - 8_10_5-check: | + cd example.org + cabal check + - 8_10_5-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_5-build: | + cd example.org + cabal build all + - 8_10_5-test: | + cd example.org + cabal test all --enable-tests + - 8_10_5-haddock: | + cd example.org + cabal haddock all + - 8_10_6-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.6 + - 8_10_6-check: | + cd example.org + cabal check + - 8_10_6-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_6-build: | + cd example.org + cabal build all + - 8_10_6-test: | + cd example.org + cabal test all --enable-tests + - 8_10_6-haddock: | + cd example.org + cabal haddock all + - 8_10_7-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.7 + - 8_10_7-check: | + cd example.org + cabal check + - 8_10_7-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_7-build: | + cd example.org + cabal build all + - 8_10_7-test: | + cd example.org + cabal test all --enable-tests + - 8_10_7-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com diff --git a/fixtures/copy-fields-all.sourcehut-parallel b/fixtures/copy-fields-all.sourcehut-parallel new file mode 100644 index 00000000..246363b0 --- /dev/null +++ b/fixtures/copy-fields-all.sourcehut-parallel @@ -0,0 +1,1552 @@ +# SUCCESS +# *INFO* Generating Sourcehut config for testing for GHC versions: 7.8.1 7.8.2 7.8.3 7.8.4 7.10.1 7.10.2 7.10.3 8.0.1 8.0.2 8.2.1 8.2.2 8.4.1 8.4.2 8.4.3 8.4.4 8.6.1 8.6.2 8.6.3 8.6.4 8.6.5 8.8.1 8.8.2 8.8.3 8.8.4 8.10.1 8.10.2 8.10.3 8.10.4 8.10.5 8.10.6 8.10.7 +# manifest name: 7.10.1 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--copy-fields=all' 'sourcehut' 'copy-fields-all.project' +# +# 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 +# +# REGENDATA ["--copy-fields=all","sourcehut","copy-fields-all.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-7.10.1 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 7_10_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.10.1 + - 7_10_1-check: | + cd example.org + cabal check + - 7_10_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_10_1-build: | + cd example.org + cabal build all + - 7_10_1-test: | + cd example.org + cabal test all --enable-tests + - 7_10_1-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 7.10.2 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--copy-fields=all' 'sourcehut' 'copy-fields-all.project' +# +# 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 +# +# REGENDATA ["--copy-fields=all","sourcehut","copy-fields-all.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-7.10.2 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 7_10_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.10.2 + - 7_10_2-check: | + cd example.org + cabal check + - 7_10_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_10_2-build: | + cd example.org + cabal build all + - 7_10_2-test: | + cd example.org + cabal test all --enable-tests + - 7_10_2-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 7.10.3 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--copy-fields=all' 'sourcehut' 'copy-fields-all.project' +# +# 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 +# +# REGENDATA ["--copy-fields=all","sourcehut","copy-fields-all.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-7.10.3 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 7_10_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.10.3 + - 7_10_3-check: | + cd example.org + cabal check + - 7_10_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_10_3-build: | + cd example.org + cabal build all + - 7_10_3-test: | + cd example.org + cabal test all --enable-tests + - 7_10_3-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 7.8.1 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--copy-fields=all' 'sourcehut' 'copy-fields-all.project' +# +# 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 +# +# REGENDATA ["--copy-fields=all","sourcehut","copy-fields-all.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-7.8.1 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 7_8_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.8.1 + - 7_8_1-check: | + cd example.org + cabal check + - 7_8_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_8_1-build: | + cd example.org + cabal build all + - 7_8_1-test: | + cd example.org + cabal test all --enable-tests + - 7_8_1-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 7.8.2 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--copy-fields=all' 'sourcehut' 'copy-fields-all.project' +# +# 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 +# +# REGENDATA ["--copy-fields=all","sourcehut","copy-fields-all.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-7.8.2 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 7_8_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.8.2 + - 7_8_2-check: | + cd example.org + cabal check + - 7_8_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_8_2-build: | + cd example.org + cabal build all + - 7_8_2-test: | + cd example.org + cabal test all --enable-tests + - 7_8_2-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 7.8.3 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--copy-fields=all' 'sourcehut' 'copy-fields-all.project' +# +# 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 +# +# REGENDATA ["--copy-fields=all","sourcehut","copy-fields-all.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-7.8.3 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 7_8_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.8.3 + - 7_8_3-check: | + cd example.org + cabal check + - 7_8_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_8_3-build: | + cd example.org + cabal build all + - 7_8_3-test: | + cd example.org + cabal test all --enable-tests + - 7_8_3-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 7.8.4 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--copy-fields=all' 'sourcehut' 'copy-fields-all.project' +# +# 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 +# +# REGENDATA ["--copy-fields=all","sourcehut","copy-fields-all.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-7.8.4 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 7_8_4-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.8.4 + - 7_8_4-check: | + cd example.org + cabal check + - 7_8_4-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_8_4-build: | + cd example.org + cabal build all + - 7_8_4-test: | + cd example.org + cabal test all --enable-tests + - 7_8_4-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.0.1 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--copy-fields=all' 'sourcehut' 'copy-fields-all.project' +# +# 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 +# +# REGENDATA ["--copy-fields=all","sourcehut","copy-fields-all.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.0.1 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_0_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.0.1 + - 8_0_1-check: | + cd example.org + cabal check + - 8_0_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_0_1-build: | + cd example.org + cabal build all + - 8_0_1-test: | + cd example.org + cabal test all --enable-tests + - 8_0_1-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.0.2 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--copy-fields=all' 'sourcehut' 'copy-fields-all.project' +# +# 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 +# +# REGENDATA ["--copy-fields=all","sourcehut","copy-fields-all.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.0.2 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_0_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.0.2 + - 8_0_2-check: | + cd example.org + cabal check + - 8_0_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_0_2-build: | + cd example.org + cabal build all + - 8_0_2-test: | + cd example.org + cabal test all --enable-tests + - 8_0_2-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.10.1 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--copy-fields=all' 'sourcehut' 'copy-fields-all.project' +# +# 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 +# +# REGENDATA ["--copy-fields=all","sourcehut","copy-fields-all.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.10.1 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_10_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.1 + - 8_10_1-check: | + cd example.org + cabal check + - 8_10_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_1-build: | + cd example.org + cabal build all + - 8_10_1-test: | + cd example.org + cabal test all --enable-tests + - 8_10_1-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.10.2 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--copy-fields=all' 'sourcehut' 'copy-fields-all.project' +# +# 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 +# +# REGENDATA ["--copy-fields=all","sourcehut","copy-fields-all.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.10.2 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_10_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.2 + - 8_10_2-check: | + cd example.org + cabal check + - 8_10_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_2-build: | + cd example.org + cabal build all + - 8_10_2-test: | + cd example.org + cabal test all --enable-tests + - 8_10_2-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.10.3 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--copy-fields=all' 'sourcehut' 'copy-fields-all.project' +# +# 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 +# +# REGENDATA ["--copy-fields=all","sourcehut","copy-fields-all.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.10.3 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_10_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.3 + - 8_10_3-check: | + cd example.org + cabal check + - 8_10_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_3-build: | + cd example.org + cabal build all + - 8_10_3-test: | + cd example.org + cabal test all --enable-tests + - 8_10_3-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.10.4 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--copy-fields=all' 'sourcehut' 'copy-fields-all.project' +# +# 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 +# +# REGENDATA ["--copy-fields=all","sourcehut","copy-fields-all.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.10.4 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_10_4-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.4 + - 8_10_4-check: | + cd example.org + cabal check + - 8_10_4-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_4-build: | + cd example.org + cabal build all + - 8_10_4-test: | + cd example.org + cabal test all --enable-tests + - 8_10_4-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.10.5 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--copy-fields=all' 'sourcehut' 'copy-fields-all.project' +# +# 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 +# +# REGENDATA ["--copy-fields=all","sourcehut","copy-fields-all.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.10.5 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_10_5-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.5 + - 8_10_5-check: | + cd example.org + cabal check + - 8_10_5-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_5-build: | + cd example.org + cabal build all + - 8_10_5-test: | + cd example.org + cabal test all --enable-tests + - 8_10_5-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.10.6 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--copy-fields=all' 'sourcehut' 'copy-fields-all.project' +# +# 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 +# +# REGENDATA ["--copy-fields=all","sourcehut","copy-fields-all.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.10.6 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_10_6-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.6 + - 8_10_6-check: | + cd example.org + cabal check + - 8_10_6-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_6-build: | + cd example.org + cabal build all + - 8_10_6-test: | + cd example.org + cabal test all --enable-tests + - 8_10_6-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.10.7 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--copy-fields=all' 'sourcehut' 'copy-fields-all.project' +# +# 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 +# +# REGENDATA ["--copy-fields=all","sourcehut","copy-fields-all.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.10.7 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_10_7-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.7 + - 8_10_7-check: | + cd example.org + cabal check + - 8_10_7-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_7-build: | + cd example.org + cabal build all + - 8_10_7-test: | + cd example.org + cabal test all --enable-tests + - 8_10_7-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.2.1 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--copy-fields=all' 'sourcehut' 'copy-fields-all.project' +# +# 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 +# +# REGENDATA ["--copy-fields=all","sourcehut","copy-fields-all.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.2.1 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_2_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.2.1 + - 8_2_1-check: | + cd example.org + cabal check + - 8_2_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_2_1-build: | + cd example.org + cabal build all + - 8_2_1-test: | + cd example.org + cabal test all --enable-tests + - 8_2_1-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.2.2 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--copy-fields=all' 'sourcehut' 'copy-fields-all.project' +# +# 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 +# +# REGENDATA ["--copy-fields=all","sourcehut","copy-fields-all.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.2.2 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_2_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.2.2 + - 8_2_2-check: | + cd example.org + cabal check + - 8_2_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_2_2-build: | + cd example.org + cabal build all + - 8_2_2-test: | + cd example.org + cabal test all --enable-tests + - 8_2_2-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.4.1 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--copy-fields=all' 'sourcehut' 'copy-fields-all.project' +# +# 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 +# +# REGENDATA ["--copy-fields=all","sourcehut","copy-fields-all.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.4.1 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_4_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.4.1 + - 8_4_1-check: | + cd example.org + cabal check + - 8_4_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_4_1-build: | + cd example.org + cabal build all + - 8_4_1-test: | + cd example.org + cabal test all --enable-tests + - 8_4_1-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.4.2 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--copy-fields=all' 'sourcehut' 'copy-fields-all.project' +# +# 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 +# +# REGENDATA ["--copy-fields=all","sourcehut","copy-fields-all.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.4.2 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_4_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.4.2 + - 8_4_2-check: | + cd example.org + cabal check + - 8_4_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_4_2-build: | + cd example.org + cabal build all + - 8_4_2-test: | + cd example.org + cabal test all --enable-tests + - 8_4_2-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.4.3 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--copy-fields=all' 'sourcehut' 'copy-fields-all.project' +# +# 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 +# +# REGENDATA ["--copy-fields=all","sourcehut","copy-fields-all.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.4.3 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_4_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.4.3 + - 8_4_3-check: | + cd example.org + cabal check + - 8_4_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_4_3-build: | + cd example.org + cabal build all + - 8_4_3-test: | + cd example.org + cabal test all --enable-tests + - 8_4_3-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.4.4 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--copy-fields=all' 'sourcehut' 'copy-fields-all.project' +# +# 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 +# +# REGENDATA ["--copy-fields=all","sourcehut","copy-fields-all.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.4.4 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_4_4-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.4.4 + - 8_4_4-check: | + cd example.org + cabal check + - 8_4_4-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_4_4-build: | + cd example.org + cabal build all + - 8_4_4-test: | + cd example.org + cabal test all --enable-tests + - 8_4_4-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.6.1 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--copy-fields=all' 'sourcehut' 'copy-fields-all.project' +# +# 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 +# +# REGENDATA ["--copy-fields=all","sourcehut","copy-fields-all.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.6.1 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_6_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.6.1 + - 8_6_1-check: | + cd example.org + cabal check + - 8_6_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_6_1-build: | + cd example.org + cabal build all + - 8_6_1-test: | + cd example.org + cabal test all --enable-tests + - 8_6_1-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.6.2 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--copy-fields=all' 'sourcehut' 'copy-fields-all.project' +# +# 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 +# +# REGENDATA ["--copy-fields=all","sourcehut","copy-fields-all.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.6.2 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_6_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.6.2 + - 8_6_2-check: | + cd example.org + cabal check + - 8_6_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_6_2-build: | + cd example.org + cabal build all + - 8_6_2-test: | + cd example.org + cabal test all --enable-tests + - 8_6_2-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.6.3 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--copy-fields=all' 'sourcehut' 'copy-fields-all.project' +# +# 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 +# +# REGENDATA ["--copy-fields=all","sourcehut","copy-fields-all.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.6.3 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_6_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.6.3 + - 8_6_3-check: | + cd example.org + cabal check + - 8_6_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_6_3-build: | + cd example.org + cabal build all + - 8_6_3-test: | + cd example.org + cabal test all --enable-tests + - 8_6_3-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.6.4 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--copy-fields=all' 'sourcehut' 'copy-fields-all.project' +# +# 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 +# +# REGENDATA ["--copy-fields=all","sourcehut","copy-fields-all.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.6.4 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_6_4-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.6.4 + - 8_6_4-check: | + cd example.org + cabal check + - 8_6_4-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_6_4-build: | + cd example.org + cabal build all + - 8_6_4-test: | + cd example.org + cabal test all --enable-tests + - 8_6_4-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.6.5 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--copy-fields=all' 'sourcehut' 'copy-fields-all.project' +# +# 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 +# +# REGENDATA ["--copy-fields=all","sourcehut","copy-fields-all.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.6.5 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_6_5-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.6.5 + - 8_6_5-check: | + cd example.org + cabal check + - 8_6_5-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_6_5-build: | + cd example.org + cabal build all + - 8_6_5-test: | + cd example.org + cabal test all --enable-tests + - 8_6_5-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.8.1 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--copy-fields=all' 'sourcehut' 'copy-fields-all.project' +# +# 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 +# +# REGENDATA ["--copy-fields=all","sourcehut","copy-fields-all.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.8.1 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_8_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.8.1 + - 8_8_1-check: | + cd example.org + cabal check + - 8_8_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_8_1-build: | + cd example.org + cabal build all + - 8_8_1-test: | + cd example.org + cabal test all --enable-tests + - 8_8_1-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.8.2 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--copy-fields=all' 'sourcehut' 'copy-fields-all.project' +# +# 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 +# +# REGENDATA ["--copy-fields=all","sourcehut","copy-fields-all.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.8.2 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_8_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.8.2 + - 8_8_2-check: | + cd example.org + cabal check + - 8_8_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_8_2-build: | + cd example.org + cabal build all + - 8_8_2-test: | + cd example.org + cabal test all --enable-tests + - 8_8_2-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.8.3 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--copy-fields=all' 'sourcehut' 'copy-fields-all.project' +# +# 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 +# +# REGENDATA ["--copy-fields=all","sourcehut","copy-fields-all.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.8.3 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_8_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.8.3 + - 8_8_3-check: | + cd example.org + cabal check + - 8_8_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_8_3-build: | + cd example.org + cabal build all + - 8_8_3-test: | + cd example.org + cabal test all --enable-tests + - 8_8_3-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.8.4 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--copy-fields=all' 'sourcehut' 'copy-fields-all.project' +# +# 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 +# +# REGENDATA ["--copy-fields=all","sourcehut","copy-fields-all.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.8.4 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_8_4-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.8.4 + - 8_8_4-check: | + cd example.org + cabal check + - 8_8_4-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_8_4-build: | + cd example.org + cabal build all + - 8_8_4-test: | + cd example.org + cabal test all --enable-tests + - 8_8_4-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com diff --git a/fixtures/copy-fields-none.sourcehut b/fixtures/copy-fields-none.sourcehut new file mode 100644 index 00000000..fa06c322 --- /dev/null +++ b/fixtures/copy-fields-none.sourcehut @@ -0,0 +1,652 @@ +# SUCCESS +# *INFO* Generating Sourcehut config for testing for GHC versions: 7.8.1 7.8.2 7.8.3 7.8.4 7.10.1 7.10.2 7.10.3 8.0.1 8.0.2 8.2.1 8.2.2 8.4.1 8.4.2 8.4.3 8.4.4 8.6.1 8.6.2 8.6.3 8.6.4 8.6.5 8.8.1 8.8.2 8.8.3 8.8.4 8.10.1 8.10.2 8.10.3 8.10.4 8.10.5 8.10.6 8.10.7 +# manifest name: all +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--copy-fields=none' 'sourcehut' 'copy-fields-none.project' +# +# 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 +# +# REGENDATA ["--copy-fields=none","sourcehut","copy-fields-none.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-7.8.1 + - ghc-7.8.2 + - ghc-7.8.3 + - ghc-7.8.4 + - ghc-7.10.1 + - ghc-7.10.2 + - ghc-7.10.3 + - ghc-8.0.1 + - ghc-8.0.2 + - ghc-8.2.1 + - ghc-8.2.2 + - ghc-8.4.1 + - ghc-8.4.2 + - ghc-8.4.3 + - ghc-8.4.4 + - ghc-8.6.1 + - ghc-8.6.2 + - ghc-8.6.3 + - ghc-8.6.4 + - ghc-8.6.5 + - ghc-8.8.1 + - ghc-8.8.2 + - ghc-8.8.3 + - ghc-8.8.4 + - ghc-8.10.1 + - ghc-8.10.2 + - ghc-8.10.3 + - ghc-8.10.4 + - ghc-8.10.5 + - ghc-8.10.6 + - ghc-8.10.7 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 7_8_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.8.1 + - 7_8_1-check: | + cd example.org + cabal check + - 7_8_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_8_1-build: | + cd example.org + cabal build all + - 7_8_1-test: | + cd example.org + cabal test all --enable-tests + - 7_8_1-haddock: | + cd example.org + cabal haddock all + - 7_8_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.8.2 + - 7_8_2-check: | + cd example.org + cabal check + - 7_8_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_8_2-build: | + cd example.org + cabal build all + - 7_8_2-test: | + cd example.org + cabal test all --enable-tests + - 7_8_2-haddock: | + cd example.org + cabal haddock all + - 7_8_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.8.3 + - 7_8_3-check: | + cd example.org + cabal check + - 7_8_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_8_3-build: | + cd example.org + cabal build all + - 7_8_3-test: | + cd example.org + cabal test all --enable-tests + - 7_8_3-haddock: | + cd example.org + cabal haddock all + - 7_8_4-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.8.4 + - 7_8_4-check: | + cd example.org + cabal check + - 7_8_4-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_8_4-build: | + cd example.org + cabal build all + - 7_8_4-test: | + cd example.org + cabal test all --enable-tests + - 7_8_4-haddock: | + cd example.org + cabal haddock all + - 7_10_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.10.1 + - 7_10_1-check: | + cd example.org + cabal check + - 7_10_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_10_1-build: | + cd example.org + cabal build all + - 7_10_1-test: | + cd example.org + cabal test all --enable-tests + - 7_10_1-haddock: | + cd example.org + cabal haddock all + - 7_10_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.10.2 + - 7_10_2-check: | + cd example.org + cabal check + - 7_10_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_10_2-build: | + cd example.org + cabal build all + - 7_10_2-test: | + cd example.org + cabal test all --enable-tests + - 7_10_2-haddock: | + cd example.org + cabal haddock all + - 7_10_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.10.3 + - 7_10_3-check: | + cd example.org + cabal check + - 7_10_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_10_3-build: | + cd example.org + cabal build all + - 7_10_3-test: | + cd example.org + cabal test all --enable-tests + - 7_10_3-haddock: | + cd example.org + cabal haddock all + - 8_0_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.0.1 + - 8_0_1-check: | + cd example.org + cabal check + - 8_0_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_0_1-build: | + cd example.org + cabal build all + - 8_0_1-test: | + cd example.org + cabal test all --enable-tests + - 8_0_1-haddock: | + cd example.org + cabal haddock all + - 8_0_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.0.2 + - 8_0_2-check: | + cd example.org + cabal check + - 8_0_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_0_2-build: | + cd example.org + cabal build all + - 8_0_2-test: | + cd example.org + cabal test all --enable-tests + - 8_0_2-haddock: | + cd example.org + cabal haddock all + - 8_2_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.2.1 + - 8_2_1-check: | + cd example.org + cabal check + - 8_2_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_2_1-build: | + cd example.org + cabal build all + - 8_2_1-test: | + cd example.org + cabal test all --enable-tests + - 8_2_1-haddock: | + cd example.org + cabal haddock all + - 8_2_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.2.2 + - 8_2_2-check: | + cd example.org + cabal check + - 8_2_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_2_2-build: | + cd example.org + cabal build all + - 8_2_2-test: | + cd example.org + cabal test all --enable-tests + - 8_2_2-haddock: | + cd example.org + cabal haddock all + - 8_4_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.4.1 + - 8_4_1-check: | + cd example.org + cabal check + - 8_4_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_4_1-build: | + cd example.org + cabal build all + - 8_4_1-test: | + cd example.org + cabal test all --enable-tests + - 8_4_1-haddock: | + cd example.org + cabal haddock all + - 8_4_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.4.2 + - 8_4_2-check: | + cd example.org + cabal check + - 8_4_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_4_2-build: | + cd example.org + cabal build all + - 8_4_2-test: | + cd example.org + cabal test all --enable-tests + - 8_4_2-haddock: | + cd example.org + cabal haddock all + - 8_4_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.4.3 + - 8_4_3-check: | + cd example.org + cabal check + - 8_4_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_4_3-build: | + cd example.org + cabal build all + - 8_4_3-test: | + cd example.org + cabal test all --enable-tests + - 8_4_3-haddock: | + cd example.org + cabal haddock all + - 8_4_4-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.4.4 + - 8_4_4-check: | + cd example.org + cabal check + - 8_4_4-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_4_4-build: | + cd example.org + cabal build all + - 8_4_4-test: | + cd example.org + cabal test all --enable-tests + - 8_4_4-haddock: | + cd example.org + cabal haddock all + - 8_6_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.6.1 + - 8_6_1-check: | + cd example.org + cabal check + - 8_6_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_6_1-build: | + cd example.org + cabal build all + - 8_6_1-test: | + cd example.org + cabal test all --enable-tests + - 8_6_1-haddock: | + cd example.org + cabal haddock all + - 8_6_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.6.2 + - 8_6_2-check: | + cd example.org + cabal check + - 8_6_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_6_2-build: | + cd example.org + cabal build all + - 8_6_2-test: | + cd example.org + cabal test all --enable-tests + - 8_6_2-haddock: | + cd example.org + cabal haddock all + - 8_6_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.6.3 + - 8_6_3-check: | + cd example.org + cabal check + - 8_6_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_6_3-build: | + cd example.org + cabal build all + - 8_6_3-test: | + cd example.org + cabal test all --enable-tests + - 8_6_3-haddock: | + cd example.org + cabal haddock all + - 8_6_4-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.6.4 + - 8_6_4-check: | + cd example.org + cabal check + - 8_6_4-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_6_4-build: | + cd example.org + cabal build all + - 8_6_4-test: | + cd example.org + cabal test all --enable-tests + - 8_6_4-haddock: | + cd example.org + cabal haddock all + - 8_6_5-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.6.5 + - 8_6_5-check: | + cd example.org + cabal check + - 8_6_5-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_6_5-build: | + cd example.org + cabal build all + - 8_6_5-test: | + cd example.org + cabal test all --enable-tests + - 8_6_5-haddock: | + cd example.org + cabal haddock all + - 8_8_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.8.1 + - 8_8_1-check: | + cd example.org + cabal check + - 8_8_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_8_1-build: | + cd example.org + cabal build all + - 8_8_1-test: | + cd example.org + cabal test all --enable-tests + - 8_8_1-haddock: | + cd example.org + cabal haddock all + - 8_8_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.8.2 + - 8_8_2-check: | + cd example.org + cabal check + - 8_8_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_8_2-build: | + cd example.org + cabal build all + - 8_8_2-test: | + cd example.org + cabal test all --enable-tests + - 8_8_2-haddock: | + cd example.org + cabal haddock all + - 8_8_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.8.3 + - 8_8_3-check: | + cd example.org + cabal check + - 8_8_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_8_3-build: | + cd example.org + cabal build all + - 8_8_3-test: | + cd example.org + cabal test all --enable-tests + - 8_8_3-haddock: | + cd example.org + cabal haddock all + - 8_8_4-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.8.4 + - 8_8_4-check: | + cd example.org + cabal check + - 8_8_4-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_8_4-build: | + cd example.org + cabal build all + - 8_8_4-test: | + cd example.org + cabal test all --enable-tests + - 8_8_4-haddock: | + cd example.org + cabal haddock all + - 8_10_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.1 + - 8_10_1-check: | + cd example.org + cabal check + - 8_10_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_1-build: | + cd example.org + cabal build all + - 8_10_1-test: | + cd example.org + cabal test all --enable-tests + - 8_10_1-haddock: | + cd example.org + cabal haddock all + - 8_10_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.2 + - 8_10_2-check: | + cd example.org + cabal check + - 8_10_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_2-build: | + cd example.org + cabal build all + - 8_10_2-test: | + cd example.org + cabal test all --enable-tests + - 8_10_2-haddock: | + cd example.org + cabal haddock all + - 8_10_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.3 + - 8_10_3-check: | + cd example.org + cabal check + - 8_10_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_3-build: | + cd example.org + cabal build all + - 8_10_3-test: | + cd example.org + cabal test all --enable-tests + - 8_10_3-haddock: | + cd example.org + cabal haddock all + - 8_10_4-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.4 + - 8_10_4-check: | + cd example.org + cabal check + - 8_10_4-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_4-build: | + cd example.org + cabal build all + - 8_10_4-test: | + cd example.org + cabal test all --enable-tests + - 8_10_4-haddock: | + cd example.org + cabal haddock all + - 8_10_5-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.5 + - 8_10_5-check: | + cd example.org + cabal check + - 8_10_5-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_5-build: | + cd example.org + cabal build all + - 8_10_5-test: | + cd example.org + cabal test all --enable-tests + - 8_10_5-haddock: | + cd example.org + cabal haddock all + - 8_10_6-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.6 + - 8_10_6-check: | + cd example.org + cabal check + - 8_10_6-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_6-build: | + cd example.org + cabal build all + - 8_10_6-test: | + cd example.org + cabal test all --enable-tests + - 8_10_6-haddock: | + cd example.org + cabal haddock all + - 8_10_7-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.7 + - 8_10_7-check: | + cd example.org + cabal check + - 8_10_7-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_7-build: | + cd example.org + cabal build all + - 8_10_7-test: | + cd example.org + cabal test all --enable-tests + - 8_10_7-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com diff --git a/fixtures/copy-fields-none.sourcehut-parallel b/fixtures/copy-fields-none.sourcehut-parallel new file mode 100644 index 00000000..5cfc358c --- /dev/null +++ b/fixtures/copy-fields-none.sourcehut-parallel @@ -0,0 +1,1552 @@ +# SUCCESS +# *INFO* Generating Sourcehut config for testing for GHC versions: 7.8.1 7.8.2 7.8.3 7.8.4 7.10.1 7.10.2 7.10.3 8.0.1 8.0.2 8.2.1 8.2.2 8.4.1 8.4.2 8.4.3 8.4.4 8.6.1 8.6.2 8.6.3 8.6.4 8.6.5 8.8.1 8.8.2 8.8.3 8.8.4 8.10.1 8.10.2 8.10.3 8.10.4 8.10.5 8.10.6 8.10.7 +# manifest name: 7.10.1 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--copy-fields=none' 'sourcehut' 'copy-fields-none.project' +# +# 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 +# +# REGENDATA ["--copy-fields=none","sourcehut","copy-fields-none.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-7.10.1 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 7_10_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.10.1 + - 7_10_1-check: | + cd example.org + cabal check + - 7_10_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_10_1-build: | + cd example.org + cabal build all + - 7_10_1-test: | + cd example.org + cabal test all --enable-tests + - 7_10_1-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 7.10.2 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--copy-fields=none' 'sourcehut' 'copy-fields-none.project' +# +# 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 +# +# REGENDATA ["--copy-fields=none","sourcehut","copy-fields-none.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-7.10.2 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 7_10_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.10.2 + - 7_10_2-check: | + cd example.org + cabal check + - 7_10_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_10_2-build: | + cd example.org + cabal build all + - 7_10_2-test: | + cd example.org + cabal test all --enable-tests + - 7_10_2-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 7.10.3 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--copy-fields=none' 'sourcehut' 'copy-fields-none.project' +# +# 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 +# +# REGENDATA ["--copy-fields=none","sourcehut","copy-fields-none.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-7.10.3 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 7_10_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.10.3 + - 7_10_3-check: | + cd example.org + cabal check + - 7_10_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_10_3-build: | + cd example.org + cabal build all + - 7_10_3-test: | + cd example.org + cabal test all --enable-tests + - 7_10_3-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 7.8.1 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--copy-fields=none' 'sourcehut' 'copy-fields-none.project' +# +# 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 +# +# REGENDATA ["--copy-fields=none","sourcehut","copy-fields-none.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-7.8.1 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 7_8_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.8.1 + - 7_8_1-check: | + cd example.org + cabal check + - 7_8_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_8_1-build: | + cd example.org + cabal build all + - 7_8_1-test: | + cd example.org + cabal test all --enable-tests + - 7_8_1-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 7.8.2 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--copy-fields=none' 'sourcehut' 'copy-fields-none.project' +# +# 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 +# +# REGENDATA ["--copy-fields=none","sourcehut","copy-fields-none.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-7.8.2 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 7_8_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.8.2 + - 7_8_2-check: | + cd example.org + cabal check + - 7_8_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_8_2-build: | + cd example.org + cabal build all + - 7_8_2-test: | + cd example.org + cabal test all --enable-tests + - 7_8_2-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 7.8.3 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--copy-fields=none' 'sourcehut' 'copy-fields-none.project' +# +# 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 +# +# REGENDATA ["--copy-fields=none","sourcehut","copy-fields-none.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-7.8.3 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 7_8_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.8.3 + - 7_8_3-check: | + cd example.org + cabal check + - 7_8_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_8_3-build: | + cd example.org + cabal build all + - 7_8_3-test: | + cd example.org + cabal test all --enable-tests + - 7_8_3-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 7.8.4 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--copy-fields=none' 'sourcehut' 'copy-fields-none.project' +# +# 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 +# +# REGENDATA ["--copy-fields=none","sourcehut","copy-fields-none.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-7.8.4 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 7_8_4-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.8.4 + - 7_8_4-check: | + cd example.org + cabal check + - 7_8_4-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_8_4-build: | + cd example.org + cabal build all + - 7_8_4-test: | + cd example.org + cabal test all --enable-tests + - 7_8_4-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.0.1 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--copy-fields=none' 'sourcehut' 'copy-fields-none.project' +# +# 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 +# +# REGENDATA ["--copy-fields=none","sourcehut","copy-fields-none.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.0.1 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_0_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.0.1 + - 8_0_1-check: | + cd example.org + cabal check + - 8_0_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_0_1-build: | + cd example.org + cabal build all + - 8_0_1-test: | + cd example.org + cabal test all --enable-tests + - 8_0_1-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.0.2 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--copy-fields=none' 'sourcehut' 'copy-fields-none.project' +# +# 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 +# +# REGENDATA ["--copy-fields=none","sourcehut","copy-fields-none.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.0.2 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_0_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.0.2 + - 8_0_2-check: | + cd example.org + cabal check + - 8_0_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_0_2-build: | + cd example.org + cabal build all + - 8_0_2-test: | + cd example.org + cabal test all --enable-tests + - 8_0_2-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.10.1 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--copy-fields=none' 'sourcehut' 'copy-fields-none.project' +# +# 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 +# +# REGENDATA ["--copy-fields=none","sourcehut","copy-fields-none.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.10.1 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_10_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.1 + - 8_10_1-check: | + cd example.org + cabal check + - 8_10_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_1-build: | + cd example.org + cabal build all + - 8_10_1-test: | + cd example.org + cabal test all --enable-tests + - 8_10_1-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.10.2 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--copy-fields=none' 'sourcehut' 'copy-fields-none.project' +# +# 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 +# +# REGENDATA ["--copy-fields=none","sourcehut","copy-fields-none.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.10.2 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_10_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.2 + - 8_10_2-check: | + cd example.org + cabal check + - 8_10_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_2-build: | + cd example.org + cabal build all + - 8_10_2-test: | + cd example.org + cabal test all --enable-tests + - 8_10_2-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.10.3 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--copy-fields=none' 'sourcehut' 'copy-fields-none.project' +# +# 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 +# +# REGENDATA ["--copy-fields=none","sourcehut","copy-fields-none.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.10.3 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_10_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.3 + - 8_10_3-check: | + cd example.org + cabal check + - 8_10_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_3-build: | + cd example.org + cabal build all + - 8_10_3-test: | + cd example.org + cabal test all --enable-tests + - 8_10_3-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.10.4 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--copy-fields=none' 'sourcehut' 'copy-fields-none.project' +# +# 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 +# +# REGENDATA ["--copy-fields=none","sourcehut","copy-fields-none.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.10.4 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_10_4-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.4 + - 8_10_4-check: | + cd example.org + cabal check + - 8_10_4-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_4-build: | + cd example.org + cabal build all + - 8_10_4-test: | + cd example.org + cabal test all --enable-tests + - 8_10_4-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.10.5 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--copy-fields=none' 'sourcehut' 'copy-fields-none.project' +# +# 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 +# +# REGENDATA ["--copy-fields=none","sourcehut","copy-fields-none.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.10.5 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_10_5-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.5 + - 8_10_5-check: | + cd example.org + cabal check + - 8_10_5-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_5-build: | + cd example.org + cabal build all + - 8_10_5-test: | + cd example.org + cabal test all --enable-tests + - 8_10_5-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.10.6 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--copy-fields=none' 'sourcehut' 'copy-fields-none.project' +# +# 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 +# +# REGENDATA ["--copy-fields=none","sourcehut","copy-fields-none.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.10.6 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_10_6-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.6 + - 8_10_6-check: | + cd example.org + cabal check + - 8_10_6-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_6-build: | + cd example.org + cabal build all + - 8_10_6-test: | + cd example.org + cabal test all --enable-tests + - 8_10_6-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.10.7 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--copy-fields=none' 'sourcehut' 'copy-fields-none.project' +# +# 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 +# +# REGENDATA ["--copy-fields=none","sourcehut","copy-fields-none.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.10.7 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_10_7-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.7 + - 8_10_7-check: | + cd example.org + cabal check + - 8_10_7-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_7-build: | + cd example.org + cabal build all + - 8_10_7-test: | + cd example.org + cabal test all --enable-tests + - 8_10_7-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.2.1 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--copy-fields=none' 'sourcehut' 'copy-fields-none.project' +# +# 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 +# +# REGENDATA ["--copy-fields=none","sourcehut","copy-fields-none.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.2.1 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_2_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.2.1 + - 8_2_1-check: | + cd example.org + cabal check + - 8_2_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_2_1-build: | + cd example.org + cabal build all + - 8_2_1-test: | + cd example.org + cabal test all --enable-tests + - 8_2_1-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.2.2 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--copy-fields=none' 'sourcehut' 'copy-fields-none.project' +# +# 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 +# +# REGENDATA ["--copy-fields=none","sourcehut","copy-fields-none.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.2.2 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_2_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.2.2 + - 8_2_2-check: | + cd example.org + cabal check + - 8_2_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_2_2-build: | + cd example.org + cabal build all + - 8_2_2-test: | + cd example.org + cabal test all --enable-tests + - 8_2_2-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.4.1 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--copy-fields=none' 'sourcehut' 'copy-fields-none.project' +# +# 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 +# +# REGENDATA ["--copy-fields=none","sourcehut","copy-fields-none.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.4.1 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_4_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.4.1 + - 8_4_1-check: | + cd example.org + cabal check + - 8_4_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_4_1-build: | + cd example.org + cabal build all + - 8_4_1-test: | + cd example.org + cabal test all --enable-tests + - 8_4_1-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.4.2 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--copy-fields=none' 'sourcehut' 'copy-fields-none.project' +# +# 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 +# +# REGENDATA ["--copy-fields=none","sourcehut","copy-fields-none.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.4.2 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_4_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.4.2 + - 8_4_2-check: | + cd example.org + cabal check + - 8_4_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_4_2-build: | + cd example.org + cabal build all + - 8_4_2-test: | + cd example.org + cabal test all --enable-tests + - 8_4_2-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.4.3 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--copy-fields=none' 'sourcehut' 'copy-fields-none.project' +# +# 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 +# +# REGENDATA ["--copy-fields=none","sourcehut","copy-fields-none.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.4.3 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_4_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.4.3 + - 8_4_3-check: | + cd example.org + cabal check + - 8_4_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_4_3-build: | + cd example.org + cabal build all + - 8_4_3-test: | + cd example.org + cabal test all --enable-tests + - 8_4_3-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.4.4 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--copy-fields=none' 'sourcehut' 'copy-fields-none.project' +# +# 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 +# +# REGENDATA ["--copy-fields=none","sourcehut","copy-fields-none.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.4.4 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_4_4-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.4.4 + - 8_4_4-check: | + cd example.org + cabal check + - 8_4_4-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_4_4-build: | + cd example.org + cabal build all + - 8_4_4-test: | + cd example.org + cabal test all --enable-tests + - 8_4_4-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.6.1 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--copy-fields=none' 'sourcehut' 'copy-fields-none.project' +# +# 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 +# +# REGENDATA ["--copy-fields=none","sourcehut","copy-fields-none.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.6.1 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_6_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.6.1 + - 8_6_1-check: | + cd example.org + cabal check + - 8_6_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_6_1-build: | + cd example.org + cabal build all + - 8_6_1-test: | + cd example.org + cabal test all --enable-tests + - 8_6_1-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.6.2 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--copy-fields=none' 'sourcehut' 'copy-fields-none.project' +# +# 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 +# +# REGENDATA ["--copy-fields=none","sourcehut","copy-fields-none.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.6.2 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_6_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.6.2 + - 8_6_2-check: | + cd example.org + cabal check + - 8_6_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_6_2-build: | + cd example.org + cabal build all + - 8_6_2-test: | + cd example.org + cabal test all --enable-tests + - 8_6_2-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.6.3 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--copy-fields=none' 'sourcehut' 'copy-fields-none.project' +# +# 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 +# +# REGENDATA ["--copy-fields=none","sourcehut","copy-fields-none.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.6.3 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_6_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.6.3 + - 8_6_3-check: | + cd example.org + cabal check + - 8_6_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_6_3-build: | + cd example.org + cabal build all + - 8_6_3-test: | + cd example.org + cabal test all --enable-tests + - 8_6_3-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.6.4 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--copy-fields=none' 'sourcehut' 'copy-fields-none.project' +# +# 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 +# +# REGENDATA ["--copy-fields=none","sourcehut","copy-fields-none.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.6.4 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_6_4-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.6.4 + - 8_6_4-check: | + cd example.org + cabal check + - 8_6_4-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_6_4-build: | + cd example.org + cabal build all + - 8_6_4-test: | + cd example.org + cabal test all --enable-tests + - 8_6_4-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.6.5 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--copy-fields=none' 'sourcehut' 'copy-fields-none.project' +# +# 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 +# +# REGENDATA ["--copy-fields=none","sourcehut","copy-fields-none.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.6.5 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_6_5-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.6.5 + - 8_6_5-check: | + cd example.org + cabal check + - 8_6_5-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_6_5-build: | + cd example.org + cabal build all + - 8_6_5-test: | + cd example.org + cabal test all --enable-tests + - 8_6_5-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.8.1 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--copy-fields=none' 'sourcehut' 'copy-fields-none.project' +# +# 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 +# +# REGENDATA ["--copy-fields=none","sourcehut","copy-fields-none.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.8.1 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_8_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.8.1 + - 8_8_1-check: | + cd example.org + cabal check + - 8_8_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_8_1-build: | + cd example.org + cabal build all + - 8_8_1-test: | + cd example.org + cabal test all --enable-tests + - 8_8_1-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.8.2 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--copy-fields=none' 'sourcehut' 'copy-fields-none.project' +# +# 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 +# +# REGENDATA ["--copy-fields=none","sourcehut","copy-fields-none.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.8.2 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_8_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.8.2 + - 8_8_2-check: | + cd example.org + cabal check + - 8_8_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_8_2-build: | + cd example.org + cabal build all + - 8_8_2-test: | + cd example.org + cabal test all --enable-tests + - 8_8_2-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.8.3 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--copy-fields=none' 'sourcehut' 'copy-fields-none.project' +# +# 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 +# +# REGENDATA ["--copy-fields=none","sourcehut","copy-fields-none.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.8.3 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_8_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.8.3 + - 8_8_3-check: | + cd example.org + cabal check + - 8_8_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_8_3-build: | + cd example.org + cabal build all + - 8_8_3-test: | + cd example.org + cabal test all --enable-tests + - 8_8_3-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.8.4 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--copy-fields=none' 'sourcehut' 'copy-fields-none.project' +# +# 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 +# +# REGENDATA ["--copy-fields=none","sourcehut","copy-fields-none.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.8.4 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_8_4-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.8.4 + - 8_8_4-check: | + cd example.org + cabal check + - 8_8_4-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_8_4-build: | + cd example.org + cabal build all + - 8_8_4-test: | + cd example.org + cabal test all --enable-tests + - 8_8_4-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com diff --git a/fixtures/copy-fields-some.sourcehut b/fixtures/copy-fields-some.sourcehut new file mode 100644 index 00000000..bd2e1260 --- /dev/null +++ b/fixtures/copy-fields-some.sourcehut @@ -0,0 +1,652 @@ +# SUCCESS +# *INFO* Generating Sourcehut config for testing for GHC versions: 7.8.1 7.8.2 7.8.3 7.8.4 7.10.1 7.10.2 7.10.3 8.0.1 8.0.2 8.2.1 8.2.2 8.4.1 8.4.2 8.4.3 8.4.4 8.6.1 8.6.2 8.6.3 8.6.4 8.6.5 8.8.1 8.8.2 8.8.3 8.8.4 8.10.1 8.10.2 8.10.3 8.10.4 8.10.5 8.10.6 8.10.7 +# manifest name: all +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--copy-fields=some' 'sourcehut' 'copy-fields-some.project' +# +# 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 +# +# REGENDATA ["--copy-fields=some","sourcehut","copy-fields-some.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-7.8.1 + - ghc-7.8.2 + - ghc-7.8.3 + - ghc-7.8.4 + - ghc-7.10.1 + - ghc-7.10.2 + - ghc-7.10.3 + - ghc-8.0.1 + - ghc-8.0.2 + - ghc-8.2.1 + - ghc-8.2.2 + - ghc-8.4.1 + - ghc-8.4.2 + - ghc-8.4.3 + - ghc-8.4.4 + - ghc-8.6.1 + - ghc-8.6.2 + - ghc-8.6.3 + - ghc-8.6.4 + - ghc-8.6.5 + - ghc-8.8.1 + - ghc-8.8.2 + - ghc-8.8.3 + - ghc-8.8.4 + - ghc-8.10.1 + - ghc-8.10.2 + - ghc-8.10.3 + - ghc-8.10.4 + - ghc-8.10.5 + - ghc-8.10.6 + - ghc-8.10.7 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 7_8_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.8.1 + - 7_8_1-check: | + cd example.org + cabal check + - 7_8_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_8_1-build: | + cd example.org + cabal build all + - 7_8_1-test: | + cd example.org + cabal test all --enable-tests + - 7_8_1-haddock: | + cd example.org + cabal haddock all + - 7_8_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.8.2 + - 7_8_2-check: | + cd example.org + cabal check + - 7_8_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_8_2-build: | + cd example.org + cabal build all + - 7_8_2-test: | + cd example.org + cabal test all --enable-tests + - 7_8_2-haddock: | + cd example.org + cabal haddock all + - 7_8_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.8.3 + - 7_8_3-check: | + cd example.org + cabal check + - 7_8_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_8_3-build: | + cd example.org + cabal build all + - 7_8_3-test: | + cd example.org + cabal test all --enable-tests + - 7_8_3-haddock: | + cd example.org + cabal haddock all + - 7_8_4-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.8.4 + - 7_8_4-check: | + cd example.org + cabal check + - 7_8_4-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_8_4-build: | + cd example.org + cabal build all + - 7_8_4-test: | + cd example.org + cabal test all --enable-tests + - 7_8_4-haddock: | + cd example.org + cabal haddock all + - 7_10_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.10.1 + - 7_10_1-check: | + cd example.org + cabal check + - 7_10_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_10_1-build: | + cd example.org + cabal build all + - 7_10_1-test: | + cd example.org + cabal test all --enable-tests + - 7_10_1-haddock: | + cd example.org + cabal haddock all + - 7_10_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.10.2 + - 7_10_2-check: | + cd example.org + cabal check + - 7_10_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_10_2-build: | + cd example.org + cabal build all + - 7_10_2-test: | + cd example.org + cabal test all --enable-tests + - 7_10_2-haddock: | + cd example.org + cabal haddock all + - 7_10_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.10.3 + - 7_10_3-check: | + cd example.org + cabal check + - 7_10_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_10_3-build: | + cd example.org + cabal build all + - 7_10_3-test: | + cd example.org + cabal test all --enable-tests + - 7_10_3-haddock: | + cd example.org + cabal haddock all + - 8_0_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.0.1 + - 8_0_1-check: | + cd example.org + cabal check + - 8_0_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_0_1-build: | + cd example.org + cabal build all + - 8_0_1-test: | + cd example.org + cabal test all --enable-tests + - 8_0_1-haddock: | + cd example.org + cabal haddock all + - 8_0_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.0.2 + - 8_0_2-check: | + cd example.org + cabal check + - 8_0_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_0_2-build: | + cd example.org + cabal build all + - 8_0_2-test: | + cd example.org + cabal test all --enable-tests + - 8_0_2-haddock: | + cd example.org + cabal haddock all + - 8_2_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.2.1 + - 8_2_1-check: | + cd example.org + cabal check + - 8_2_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_2_1-build: | + cd example.org + cabal build all + - 8_2_1-test: | + cd example.org + cabal test all --enable-tests + - 8_2_1-haddock: | + cd example.org + cabal haddock all + - 8_2_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.2.2 + - 8_2_2-check: | + cd example.org + cabal check + - 8_2_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_2_2-build: | + cd example.org + cabal build all + - 8_2_2-test: | + cd example.org + cabal test all --enable-tests + - 8_2_2-haddock: | + cd example.org + cabal haddock all + - 8_4_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.4.1 + - 8_4_1-check: | + cd example.org + cabal check + - 8_4_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_4_1-build: | + cd example.org + cabal build all + - 8_4_1-test: | + cd example.org + cabal test all --enable-tests + - 8_4_1-haddock: | + cd example.org + cabal haddock all + - 8_4_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.4.2 + - 8_4_2-check: | + cd example.org + cabal check + - 8_4_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_4_2-build: | + cd example.org + cabal build all + - 8_4_2-test: | + cd example.org + cabal test all --enable-tests + - 8_4_2-haddock: | + cd example.org + cabal haddock all + - 8_4_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.4.3 + - 8_4_3-check: | + cd example.org + cabal check + - 8_4_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_4_3-build: | + cd example.org + cabal build all + - 8_4_3-test: | + cd example.org + cabal test all --enable-tests + - 8_4_3-haddock: | + cd example.org + cabal haddock all + - 8_4_4-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.4.4 + - 8_4_4-check: | + cd example.org + cabal check + - 8_4_4-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_4_4-build: | + cd example.org + cabal build all + - 8_4_4-test: | + cd example.org + cabal test all --enable-tests + - 8_4_4-haddock: | + cd example.org + cabal haddock all + - 8_6_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.6.1 + - 8_6_1-check: | + cd example.org + cabal check + - 8_6_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_6_1-build: | + cd example.org + cabal build all + - 8_6_1-test: | + cd example.org + cabal test all --enable-tests + - 8_6_1-haddock: | + cd example.org + cabal haddock all + - 8_6_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.6.2 + - 8_6_2-check: | + cd example.org + cabal check + - 8_6_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_6_2-build: | + cd example.org + cabal build all + - 8_6_2-test: | + cd example.org + cabal test all --enable-tests + - 8_6_2-haddock: | + cd example.org + cabal haddock all + - 8_6_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.6.3 + - 8_6_3-check: | + cd example.org + cabal check + - 8_6_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_6_3-build: | + cd example.org + cabal build all + - 8_6_3-test: | + cd example.org + cabal test all --enable-tests + - 8_6_3-haddock: | + cd example.org + cabal haddock all + - 8_6_4-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.6.4 + - 8_6_4-check: | + cd example.org + cabal check + - 8_6_4-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_6_4-build: | + cd example.org + cabal build all + - 8_6_4-test: | + cd example.org + cabal test all --enable-tests + - 8_6_4-haddock: | + cd example.org + cabal haddock all + - 8_6_5-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.6.5 + - 8_6_5-check: | + cd example.org + cabal check + - 8_6_5-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_6_5-build: | + cd example.org + cabal build all + - 8_6_5-test: | + cd example.org + cabal test all --enable-tests + - 8_6_5-haddock: | + cd example.org + cabal haddock all + - 8_8_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.8.1 + - 8_8_1-check: | + cd example.org + cabal check + - 8_8_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_8_1-build: | + cd example.org + cabal build all + - 8_8_1-test: | + cd example.org + cabal test all --enable-tests + - 8_8_1-haddock: | + cd example.org + cabal haddock all + - 8_8_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.8.2 + - 8_8_2-check: | + cd example.org + cabal check + - 8_8_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_8_2-build: | + cd example.org + cabal build all + - 8_8_2-test: | + cd example.org + cabal test all --enable-tests + - 8_8_2-haddock: | + cd example.org + cabal haddock all + - 8_8_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.8.3 + - 8_8_3-check: | + cd example.org + cabal check + - 8_8_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_8_3-build: | + cd example.org + cabal build all + - 8_8_3-test: | + cd example.org + cabal test all --enable-tests + - 8_8_3-haddock: | + cd example.org + cabal haddock all + - 8_8_4-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.8.4 + - 8_8_4-check: | + cd example.org + cabal check + - 8_8_4-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_8_4-build: | + cd example.org + cabal build all + - 8_8_4-test: | + cd example.org + cabal test all --enable-tests + - 8_8_4-haddock: | + cd example.org + cabal haddock all + - 8_10_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.1 + - 8_10_1-check: | + cd example.org + cabal check + - 8_10_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_1-build: | + cd example.org + cabal build all + - 8_10_1-test: | + cd example.org + cabal test all --enable-tests + - 8_10_1-haddock: | + cd example.org + cabal haddock all + - 8_10_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.2 + - 8_10_2-check: | + cd example.org + cabal check + - 8_10_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_2-build: | + cd example.org + cabal build all + - 8_10_2-test: | + cd example.org + cabal test all --enable-tests + - 8_10_2-haddock: | + cd example.org + cabal haddock all + - 8_10_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.3 + - 8_10_3-check: | + cd example.org + cabal check + - 8_10_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_3-build: | + cd example.org + cabal build all + - 8_10_3-test: | + cd example.org + cabal test all --enable-tests + - 8_10_3-haddock: | + cd example.org + cabal haddock all + - 8_10_4-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.4 + - 8_10_4-check: | + cd example.org + cabal check + - 8_10_4-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_4-build: | + cd example.org + cabal build all + - 8_10_4-test: | + cd example.org + cabal test all --enable-tests + - 8_10_4-haddock: | + cd example.org + cabal haddock all + - 8_10_5-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.5 + - 8_10_5-check: | + cd example.org + cabal check + - 8_10_5-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_5-build: | + cd example.org + cabal build all + - 8_10_5-test: | + cd example.org + cabal test all --enable-tests + - 8_10_5-haddock: | + cd example.org + cabal haddock all + - 8_10_6-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.6 + - 8_10_6-check: | + cd example.org + cabal check + - 8_10_6-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_6-build: | + cd example.org + cabal build all + - 8_10_6-test: | + cd example.org + cabal test all --enable-tests + - 8_10_6-haddock: | + cd example.org + cabal haddock all + - 8_10_7-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.7 + - 8_10_7-check: | + cd example.org + cabal check + - 8_10_7-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_7-build: | + cd example.org + cabal build all + - 8_10_7-test: | + cd example.org + cabal test all --enable-tests + - 8_10_7-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com diff --git a/fixtures/copy-fields-some.sourcehut-parallel b/fixtures/copy-fields-some.sourcehut-parallel new file mode 100644 index 00000000..39a3c3d8 --- /dev/null +++ b/fixtures/copy-fields-some.sourcehut-parallel @@ -0,0 +1,1552 @@ +# SUCCESS +# *INFO* Generating Sourcehut config for testing for GHC versions: 7.8.1 7.8.2 7.8.3 7.8.4 7.10.1 7.10.2 7.10.3 8.0.1 8.0.2 8.2.1 8.2.2 8.4.1 8.4.2 8.4.3 8.4.4 8.6.1 8.6.2 8.6.3 8.6.4 8.6.5 8.8.1 8.8.2 8.8.3 8.8.4 8.10.1 8.10.2 8.10.3 8.10.4 8.10.5 8.10.6 8.10.7 +# manifest name: 7.10.1 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--copy-fields=some' 'sourcehut' 'copy-fields-some.project' +# +# 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 +# +# REGENDATA ["--copy-fields=some","sourcehut","copy-fields-some.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-7.10.1 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 7_10_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.10.1 + - 7_10_1-check: | + cd example.org + cabal check + - 7_10_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_10_1-build: | + cd example.org + cabal build all + - 7_10_1-test: | + cd example.org + cabal test all --enable-tests + - 7_10_1-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 7.10.2 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--copy-fields=some' 'sourcehut' 'copy-fields-some.project' +# +# 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 +# +# REGENDATA ["--copy-fields=some","sourcehut","copy-fields-some.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-7.10.2 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 7_10_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.10.2 + - 7_10_2-check: | + cd example.org + cabal check + - 7_10_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_10_2-build: | + cd example.org + cabal build all + - 7_10_2-test: | + cd example.org + cabal test all --enable-tests + - 7_10_2-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 7.10.3 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--copy-fields=some' 'sourcehut' 'copy-fields-some.project' +# +# 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 +# +# REGENDATA ["--copy-fields=some","sourcehut","copy-fields-some.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-7.10.3 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 7_10_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.10.3 + - 7_10_3-check: | + cd example.org + cabal check + - 7_10_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_10_3-build: | + cd example.org + cabal build all + - 7_10_3-test: | + cd example.org + cabal test all --enable-tests + - 7_10_3-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 7.8.1 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--copy-fields=some' 'sourcehut' 'copy-fields-some.project' +# +# 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 +# +# REGENDATA ["--copy-fields=some","sourcehut","copy-fields-some.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-7.8.1 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 7_8_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.8.1 + - 7_8_1-check: | + cd example.org + cabal check + - 7_8_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_8_1-build: | + cd example.org + cabal build all + - 7_8_1-test: | + cd example.org + cabal test all --enable-tests + - 7_8_1-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 7.8.2 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--copy-fields=some' 'sourcehut' 'copy-fields-some.project' +# +# 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 +# +# REGENDATA ["--copy-fields=some","sourcehut","copy-fields-some.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-7.8.2 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 7_8_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.8.2 + - 7_8_2-check: | + cd example.org + cabal check + - 7_8_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_8_2-build: | + cd example.org + cabal build all + - 7_8_2-test: | + cd example.org + cabal test all --enable-tests + - 7_8_2-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 7.8.3 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--copy-fields=some' 'sourcehut' 'copy-fields-some.project' +# +# 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 +# +# REGENDATA ["--copy-fields=some","sourcehut","copy-fields-some.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-7.8.3 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 7_8_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.8.3 + - 7_8_3-check: | + cd example.org + cabal check + - 7_8_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_8_3-build: | + cd example.org + cabal build all + - 7_8_3-test: | + cd example.org + cabal test all --enable-tests + - 7_8_3-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 7.8.4 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--copy-fields=some' 'sourcehut' 'copy-fields-some.project' +# +# 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 +# +# REGENDATA ["--copy-fields=some","sourcehut","copy-fields-some.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-7.8.4 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 7_8_4-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.8.4 + - 7_8_4-check: | + cd example.org + cabal check + - 7_8_4-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_8_4-build: | + cd example.org + cabal build all + - 7_8_4-test: | + cd example.org + cabal test all --enable-tests + - 7_8_4-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.0.1 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--copy-fields=some' 'sourcehut' 'copy-fields-some.project' +# +# 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 +# +# REGENDATA ["--copy-fields=some","sourcehut","copy-fields-some.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.0.1 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_0_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.0.1 + - 8_0_1-check: | + cd example.org + cabal check + - 8_0_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_0_1-build: | + cd example.org + cabal build all + - 8_0_1-test: | + cd example.org + cabal test all --enable-tests + - 8_0_1-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.0.2 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--copy-fields=some' 'sourcehut' 'copy-fields-some.project' +# +# 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 +# +# REGENDATA ["--copy-fields=some","sourcehut","copy-fields-some.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.0.2 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_0_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.0.2 + - 8_0_2-check: | + cd example.org + cabal check + - 8_0_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_0_2-build: | + cd example.org + cabal build all + - 8_0_2-test: | + cd example.org + cabal test all --enable-tests + - 8_0_2-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.10.1 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--copy-fields=some' 'sourcehut' 'copy-fields-some.project' +# +# 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 +# +# REGENDATA ["--copy-fields=some","sourcehut","copy-fields-some.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.10.1 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_10_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.1 + - 8_10_1-check: | + cd example.org + cabal check + - 8_10_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_1-build: | + cd example.org + cabal build all + - 8_10_1-test: | + cd example.org + cabal test all --enable-tests + - 8_10_1-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.10.2 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--copy-fields=some' 'sourcehut' 'copy-fields-some.project' +# +# 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 +# +# REGENDATA ["--copy-fields=some","sourcehut","copy-fields-some.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.10.2 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_10_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.2 + - 8_10_2-check: | + cd example.org + cabal check + - 8_10_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_2-build: | + cd example.org + cabal build all + - 8_10_2-test: | + cd example.org + cabal test all --enable-tests + - 8_10_2-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.10.3 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--copy-fields=some' 'sourcehut' 'copy-fields-some.project' +# +# 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 +# +# REGENDATA ["--copy-fields=some","sourcehut","copy-fields-some.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.10.3 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_10_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.3 + - 8_10_3-check: | + cd example.org + cabal check + - 8_10_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_3-build: | + cd example.org + cabal build all + - 8_10_3-test: | + cd example.org + cabal test all --enable-tests + - 8_10_3-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.10.4 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--copy-fields=some' 'sourcehut' 'copy-fields-some.project' +# +# 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 +# +# REGENDATA ["--copy-fields=some","sourcehut","copy-fields-some.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.10.4 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_10_4-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.4 + - 8_10_4-check: | + cd example.org + cabal check + - 8_10_4-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_4-build: | + cd example.org + cabal build all + - 8_10_4-test: | + cd example.org + cabal test all --enable-tests + - 8_10_4-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.10.5 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--copy-fields=some' 'sourcehut' 'copy-fields-some.project' +# +# 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 +# +# REGENDATA ["--copy-fields=some","sourcehut","copy-fields-some.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.10.5 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_10_5-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.5 + - 8_10_5-check: | + cd example.org + cabal check + - 8_10_5-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_5-build: | + cd example.org + cabal build all + - 8_10_5-test: | + cd example.org + cabal test all --enable-tests + - 8_10_5-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.10.6 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--copy-fields=some' 'sourcehut' 'copy-fields-some.project' +# +# 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 +# +# REGENDATA ["--copy-fields=some","sourcehut","copy-fields-some.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.10.6 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_10_6-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.6 + - 8_10_6-check: | + cd example.org + cabal check + - 8_10_6-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_6-build: | + cd example.org + cabal build all + - 8_10_6-test: | + cd example.org + cabal test all --enable-tests + - 8_10_6-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.10.7 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--copy-fields=some' 'sourcehut' 'copy-fields-some.project' +# +# 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 +# +# REGENDATA ["--copy-fields=some","sourcehut","copy-fields-some.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.10.7 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_10_7-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.7 + - 8_10_7-check: | + cd example.org + cabal check + - 8_10_7-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_7-build: | + cd example.org + cabal build all + - 8_10_7-test: | + cd example.org + cabal test all --enable-tests + - 8_10_7-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.2.1 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--copy-fields=some' 'sourcehut' 'copy-fields-some.project' +# +# 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 +# +# REGENDATA ["--copy-fields=some","sourcehut","copy-fields-some.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.2.1 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_2_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.2.1 + - 8_2_1-check: | + cd example.org + cabal check + - 8_2_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_2_1-build: | + cd example.org + cabal build all + - 8_2_1-test: | + cd example.org + cabal test all --enable-tests + - 8_2_1-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.2.2 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--copy-fields=some' 'sourcehut' 'copy-fields-some.project' +# +# 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 +# +# REGENDATA ["--copy-fields=some","sourcehut","copy-fields-some.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.2.2 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_2_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.2.2 + - 8_2_2-check: | + cd example.org + cabal check + - 8_2_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_2_2-build: | + cd example.org + cabal build all + - 8_2_2-test: | + cd example.org + cabal test all --enable-tests + - 8_2_2-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.4.1 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--copy-fields=some' 'sourcehut' 'copy-fields-some.project' +# +# 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 +# +# REGENDATA ["--copy-fields=some","sourcehut","copy-fields-some.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.4.1 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_4_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.4.1 + - 8_4_1-check: | + cd example.org + cabal check + - 8_4_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_4_1-build: | + cd example.org + cabal build all + - 8_4_1-test: | + cd example.org + cabal test all --enable-tests + - 8_4_1-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.4.2 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--copy-fields=some' 'sourcehut' 'copy-fields-some.project' +# +# 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 +# +# REGENDATA ["--copy-fields=some","sourcehut","copy-fields-some.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.4.2 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_4_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.4.2 + - 8_4_2-check: | + cd example.org + cabal check + - 8_4_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_4_2-build: | + cd example.org + cabal build all + - 8_4_2-test: | + cd example.org + cabal test all --enable-tests + - 8_4_2-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.4.3 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--copy-fields=some' 'sourcehut' 'copy-fields-some.project' +# +# 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 +# +# REGENDATA ["--copy-fields=some","sourcehut","copy-fields-some.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.4.3 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_4_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.4.3 + - 8_4_3-check: | + cd example.org + cabal check + - 8_4_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_4_3-build: | + cd example.org + cabal build all + - 8_4_3-test: | + cd example.org + cabal test all --enable-tests + - 8_4_3-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.4.4 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--copy-fields=some' 'sourcehut' 'copy-fields-some.project' +# +# 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 +# +# REGENDATA ["--copy-fields=some","sourcehut","copy-fields-some.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.4.4 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_4_4-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.4.4 + - 8_4_4-check: | + cd example.org + cabal check + - 8_4_4-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_4_4-build: | + cd example.org + cabal build all + - 8_4_4-test: | + cd example.org + cabal test all --enable-tests + - 8_4_4-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.6.1 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--copy-fields=some' 'sourcehut' 'copy-fields-some.project' +# +# 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 +# +# REGENDATA ["--copy-fields=some","sourcehut","copy-fields-some.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.6.1 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_6_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.6.1 + - 8_6_1-check: | + cd example.org + cabal check + - 8_6_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_6_1-build: | + cd example.org + cabal build all + - 8_6_1-test: | + cd example.org + cabal test all --enable-tests + - 8_6_1-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.6.2 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--copy-fields=some' 'sourcehut' 'copy-fields-some.project' +# +# 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 +# +# REGENDATA ["--copy-fields=some","sourcehut","copy-fields-some.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.6.2 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_6_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.6.2 + - 8_6_2-check: | + cd example.org + cabal check + - 8_6_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_6_2-build: | + cd example.org + cabal build all + - 8_6_2-test: | + cd example.org + cabal test all --enable-tests + - 8_6_2-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.6.3 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--copy-fields=some' 'sourcehut' 'copy-fields-some.project' +# +# 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 +# +# REGENDATA ["--copy-fields=some","sourcehut","copy-fields-some.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.6.3 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_6_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.6.3 + - 8_6_3-check: | + cd example.org + cabal check + - 8_6_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_6_3-build: | + cd example.org + cabal build all + - 8_6_3-test: | + cd example.org + cabal test all --enable-tests + - 8_6_3-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.6.4 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--copy-fields=some' 'sourcehut' 'copy-fields-some.project' +# +# 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 +# +# REGENDATA ["--copy-fields=some","sourcehut","copy-fields-some.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.6.4 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_6_4-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.6.4 + - 8_6_4-check: | + cd example.org + cabal check + - 8_6_4-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_6_4-build: | + cd example.org + cabal build all + - 8_6_4-test: | + cd example.org + cabal test all --enable-tests + - 8_6_4-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.6.5 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--copy-fields=some' 'sourcehut' 'copy-fields-some.project' +# +# 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 +# +# REGENDATA ["--copy-fields=some","sourcehut","copy-fields-some.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.6.5 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_6_5-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.6.5 + - 8_6_5-check: | + cd example.org + cabal check + - 8_6_5-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_6_5-build: | + cd example.org + cabal build all + - 8_6_5-test: | + cd example.org + cabal test all --enable-tests + - 8_6_5-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.8.1 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--copy-fields=some' 'sourcehut' 'copy-fields-some.project' +# +# 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 +# +# REGENDATA ["--copy-fields=some","sourcehut","copy-fields-some.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.8.1 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_8_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.8.1 + - 8_8_1-check: | + cd example.org + cabal check + - 8_8_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_8_1-build: | + cd example.org + cabal build all + - 8_8_1-test: | + cd example.org + cabal test all --enable-tests + - 8_8_1-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.8.2 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--copy-fields=some' 'sourcehut' 'copy-fields-some.project' +# +# 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 +# +# REGENDATA ["--copy-fields=some","sourcehut","copy-fields-some.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.8.2 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_8_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.8.2 + - 8_8_2-check: | + cd example.org + cabal check + - 8_8_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_8_2-build: | + cd example.org + cabal build all + - 8_8_2-test: | + cd example.org + cabal test all --enable-tests + - 8_8_2-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.8.3 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--copy-fields=some' 'sourcehut' 'copy-fields-some.project' +# +# 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 +# +# REGENDATA ["--copy-fields=some","sourcehut","copy-fields-some.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.8.3 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_8_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.8.3 + - 8_8_3-check: | + cd example.org + cabal check + - 8_8_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_8_3-build: | + cd example.org + cabal build all + - 8_8_3-test: | + cd example.org + cabal test all --enable-tests + - 8_8_3-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.8.4 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--copy-fields=some' 'sourcehut' 'copy-fields-some.project' +# +# 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 +# +# REGENDATA ["--copy-fields=some","sourcehut","copy-fields-some.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.8.4 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_8_4-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.8.4 + - 8_8_4-check: | + cd example.org + cabal check + - 8_8_4-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_8_4-build: | + cd example.org + cabal build all + - 8_8_4-test: | + cd example.org + cabal test all --enable-tests + - 8_8_4-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com diff --git a/fixtures/empty-line.sourcehut b/fixtures/empty-line.sourcehut new file mode 100644 index 00000000..f7c43dbf --- /dev/null +++ b/fixtures/empty-line.sourcehut @@ -0,0 +1,672 @@ +# SUCCESS +# *INFO* Generating Sourcehut config for testing for GHC versions: ghc-head 7.8.1 7.8.2 7.8.3 7.8.4 7.10.1 7.10.2 7.10.3 8.0.1 8.0.2 8.2.1 8.2.2 8.4.1 8.4.2 8.4.3 8.4.4 8.6.1 8.6.2 8.6.3 8.6.4 8.6.5 8.8.1 8.8.2 8.8.3 8.8.4 8.10.1 8.10.2 8.10.3 8.10.4 8.10.5 8.10.6 8.10.7 +# manifest name: all +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--ghc-head' 'sourcehut' 'empty-line.project' +# +# 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 +# +# REGENDATA ["--ghc-head","sourcehut","empty-line.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-head + - ghc-7.8.1 + - ghc-7.8.2 + - ghc-7.8.3 + - ghc-7.8.4 + - ghc-7.10.1 + - ghc-7.10.2 + - ghc-7.10.3 + - ghc-8.0.1 + - ghc-8.0.2 + - ghc-8.2.1 + - ghc-8.2.2 + - ghc-8.4.1 + - ghc-8.4.2 + - ghc-8.4.3 + - ghc-8.4.4 + - ghc-8.6.1 + - ghc-8.6.2 + - ghc-8.6.3 + - ghc-8.6.4 + - ghc-8.6.5 + - ghc-8.8.1 + - ghc-8.8.2 + - ghc-8.8.3 + - ghc-8.8.4 + - ghc-8.10.1 + - ghc-8.10.2 + - ghc-8.10.3 + - ghc-8.10.4 + - ghc-8.10.5 + - ghc-8.10.6 + - ghc-8.10.7 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - ghc-head-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-head + - ghc-head-check: | + cd example.org + cabal check + - ghc-head-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - ghc-head-build: | + cd example.org + cabal build all + - ghc-head-test: | + cd example.org + cabal test all --enable-tests + - ghc-head-haddock: | + cd example.org + cabal haddock all + - 7_8_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.8.1 + - 7_8_1-check: | + cd example.org + cabal check + - 7_8_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_8_1-build: | + cd example.org + cabal build all + - 7_8_1-test: | + cd example.org + cabal test all --enable-tests + - 7_8_1-haddock: | + cd example.org + cabal haddock all + - 7_8_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.8.2 + - 7_8_2-check: | + cd example.org + cabal check + - 7_8_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_8_2-build: | + cd example.org + cabal build all + - 7_8_2-test: | + cd example.org + cabal test all --enable-tests + - 7_8_2-haddock: | + cd example.org + cabal haddock all + - 7_8_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.8.3 + - 7_8_3-check: | + cd example.org + cabal check + - 7_8_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_8_3-build: | + cd example.org + cabal build all + - 7_8_3-test: | + cd example.org + cabal test all --enable-tests + - 7_8_3-haddock: | + cd example.org + cabal haddock all + - 7_8_4-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.8.4 + - 7_8_4-check: | + cd example.org + cabal check + - 7_8_4-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_8_4-build: | + cd example.org + cabal build all + - 7_8_4-test: | + cd example.org + cabal test all --enable-tests + - 7_8_4-haddock: | + cd example.org + cabal haddock all + - 7_10_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.10.1 + - 7_10_1-check: | + cd example.org + cabal check + - 7_10_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_10_1-build: | + cd example.org + cabal build all + - 7_10_1-test: | + cd example.org + cabal test all --enable-tests + - 7_10_1-haddock: | + cd example.org + cabal haddock all + - 7_10_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.10.2 + - 7_10_2-check: | + cd example.org + cabal check + - 7_10_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_10_2-build: | + cd example.org + cabal build all + - 7_10_2-test: | + cd example.org + cabal test all --enable-tests + - 7_10_2-haddock: | + cd example.org + cabal haddock all + - 7_10_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.10.3 + - 7_10_3-check: | + cd example.org + cabal check + - 7_10_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_10_3-build: | + cd example.org + cabal build all + - 7_10_3-test: | + cd example.org + cabal test all --enable-tests + - 7_10_3-haddock: | + cd example.org + cabal haddock all + - 8_0_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.0.1 + - 8_0_1-check: | + cd example.org + cabal check + - 8_0_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_0_1-build: | + cd example.org + cabal build all + - 8_0_1-test: | + cd example.org + cabal test all --enable-tests + - 8_0_1-haddock: | + cd example.org + cabal haddock all + - 8_0_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.0.2 + - 8_0_2-check: | + cd example.org + cabal check + - 8_0_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_0_2-build: | + cd example.org + cabal build all + - 8_0_2-test: | + cd example.org + cabal test all --enable-tests + - 8_0_2-haddock: | + cd example.org + cabal haddock all + - 8_2_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.2.1 + - 8_2_1-check: | + cd example.org + cabal check + - 8_2_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_2_1-build: | + cd example.org + cabal build all + - 8_2_1-test: | + cd example.org + cabal test all --enable-tests + - 8_2_1-haddock: | + cd example.org + cabal haddock all + - 8_2_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.2.2 + - 8_2_2-check: | + cd example.org + cabal check + - 8_2_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_2_2-build: | + cd example.org + cabal build all + - 8_2_2-test: | + cd example.org + cabal test all --enable-tests + - 8_2_2-haddock: | + cd example.org + cabal haddock all + - 8_4_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.4.1 + - 8_4_1-check: | + cd example.org + cabal check + - 8_4_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_4_1-build: | + cd example.org + cabal build all + - 8_4_1-test: | + cd example.org + cabal test all --enable-tests + - 8_4_1-haddock: | + cd example.org + cabal haddock all + - 8_4_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.4.2 + - 8_4_2-check: | + cd example.org + cabal check + - 8_4_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_4_2-build: | + cd example.org + cabal build all + - 8_4_2-test: | + cd example.org + cabal test all --enable-tests + - 8_4_2-haddock: | + cd example.org + cabal haddock all + - 8_4_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.4.3 + - 8_4_3-check: | + cd example.org + cabal check + - 8_4_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_4_3-build: | + cd example.org + cabal build all + - 8_4_3-test: | + cd example.org + cabal test all --enable-tests + - 8_4_3-haddock: | + cd example.org + cabal haddock all + - 8_4_4-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.4.4 + - 8_4_4-check: | + cd example.org + cabal check + - 8_4_4-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_4_4-build: | + cd example.org + cabal build all + - 8_4_4-test: | + cd example.org + cabal test all --enable-tests + - 8_4_4-haddock: | + cd example.org + cabal haddock all + - 8_6_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.6.1 + - 8_6_1-check: | + cd example.org + cabal check + - 8_6_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_6_1-build: | + cd example.org + cabal build all + - 8_6_1-test: | + cd example.org + cabal test all --enable-tests + - 8_6_1-haddock: | + cd example.org + cabal haddock all + - 8_6_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.6.2 + - 8_6_2-check: | + cd example.org + cabal check + - 8_6_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_6_2-build: | + cd example.org + cabal build all + - 8_6_2-test: | + cd example.org + cabal test all --enable-tests + - 8_6_2-haddock: | + cd example.org + cabal haddock all + - 8_6_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.6.3 + - 8_6_3-check: | + cd example.org + cabal check + - 8_6_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_6_3-build: | + cd example.org + cabal build all + - 8_6_3-test: | + cd example.org + cabal test all --enable-tests + - 8_6_3-haddock: | + cd example.org + cabal haddock all + - 8_6_4-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.6.4 + - 8_6_4-check: | + cd example.org + cabal check + - 8_6_4-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_6_4-build: | + cd example.org + cabal build all + - 8_6_4-test: | + cd example.org + cabal test all --enable-tests + - 8_6_4-haddock: | + cd example.org + cabal haddock all + - 8_6_5-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.6.5 + - 8_6_5-check: | + cd example.org + cabal check + - 8_6_5-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_6_5-build: | + cd example.org + cabal build all + - 8_6_5-test: | + cd example.org + cabal test all --enable-tests + - 8_6_5-haddock: | + cd example.org + cabal haddock all + - 8_8_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.8.1 + - 8_8_1-check: | + cd example.org + cabal check + - 8_8_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_8_1-build: | + cd example.org + cabal build all + - 8_8_1-test: | + cd example.org + cabal test all --enable-tests + - 8_8_1-haddock: | + cd example.org + cabal haddock all + - 8_8_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.8.2 + - 8_8_2-check: | + cd example.org + cabal check + - 8_8_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_8_2-build: | + cd example.org + cabal build all + - 8_8_2-test: | + cd example.org + cabal test all --enable-tests + - 8_8_2-haddock: | + cd example.org + cabal haddock all + - 8_8_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.8.3 + - 8_8_3-check: | + cd example.org + cabal check + - 8_8_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_8_3-build: | + cd example.org + cabal build all + - 8_8_3-test: | + cd example.org + cabal test all --enable-tests + - 8_8_3-haddock: | + cd example.org + cabal haddock all + - 8_8_4-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.8.4 + - 8_8_4-check: | + cd example.org + cabal check + - 8_8_4-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_8_4-build: | + cd example.org + cabal build all + - 8_8_4-test: | + cd example.org + cabal test all --enable-tests + - 8_8_4-haddock: | + cd example.org + cabal haddock all + - 8_10_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.1 + - 8_10_1-check: | + cd example.org + cabal check + - 8_10_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_1-build: | + cd example.org + cabal build all + - 8_10_1-test: | + cd example.org + cabal test all --enable-tests + - 8_10_1-haddock: | + cd example.org + cabal haddock all + - 8_10_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.2 + - 8_10_2-check: | + cd example.org + cabal check + - 8_10_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_2-build: | + cd example.org + cabal build all + - 8_10_2-test: | + cd example.org + cabal test all --enable-tests + - 8_10_2-haddock: | + cd example.org + cabal haddock all + - 8_10_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.3 + - 8_10_3-check: | + cd example.org + cabal check + - 8_10_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_3-build: | + cd example.org + cabal build all + - 8_10_3-test: | + cd example.org + cabal test all --enable-tests + - 8_10_3-haddock: | + cd example.org + cabal haddock all + - 8_10_4-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.4 + - 8_10_4-check: | + cd example.org + cabal check + - 8_10_4-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_4-build: | + cd example.org + cabal build all + - 8_10_4-test: | + cd example.org + cabal test all --enable-tests + - 8_10_4-haddock: | + cd example.org + cabal haddock all + - 8_10_5-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.5 + - 8_10_5-check: | + cd example.org + cabal check + - 8_10_5-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_5-build: | + cd example.org + cabal build all + - 8_10_5-test: | + cd example.org + cabal test all --enable-tests + - 8_10_5-haddock: | + cd example.org + cabal haddock all + - 8_10_6-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.6 + - 8_10_6-check: | + cd example.org + cabal check + - 8_10_6-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_6-build: | + cd example.org + cabal build all + - 8_10_6-test: | + cd example.org + cabal test all --enable-tests + - 8_10_6-haddock: | + cd example.org + cabal haddock all + - 8_10_7-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.7 + - 8_10_7-check: | + cd example.org + cabal check + - 8_10_7-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_7-build: | + cd example.org + cabal build all + - 8_10_7-test: | + cd example.org + cabal test all --enable-tests + - 8_10_7-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com diff --git a/fixtures/empty-line.sourcehut-parallel b/fixtures/empty-line.sourcehut-parallel new file mode 100644 index 00000000..2378067d --- /dev/null +++ b/fixtures/empty-line.sourcehut-parallel @@ -0,0 +1,1602 @@ +# SUCCESS +# *INFO* Generating Sourcehut config for testing for GHC versions: ghc-head 7.8.1 7.8.2 7.8.3 7.8.4 7.10.1 7.10.2 7.10.3 8.0.1 8.0.2 8.2.1 8.2.2 8.4.1 8.4.2 8.4.3 8.4.4 8.6.1 8.6.2 8.6.3 8.6.4 8.6.5 8.8.1 8.8.2 8.8.3 8.8.4 8.10.1 8.10.2 8.10.3 8.10.4 8.10.5 8.10.6 8.10.7 +# manifest name: 7.10.1 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--ghc-head' 'sourcehut' 'empty-line.project' +# +# 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 +# +# REGENDATA ["--ghc-head","sourcehut","empty-line.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-7.10.1 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 7_10_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.10.1 + - 7_10_1-check: | + cd example.org + cabal check + - 7_10_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_10_1-build: | + cd example.org + cabal build all + - 7_10_1-test: | + cd example.org + cabal test all --enable-tests + - 7_10_1-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 7.10.2 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--ghc-head' 'sourcehut' 'empty-line.project' +# +# 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 +# +# REGENDATA ["--ghc-head","sourcehut","empty-line.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-7.10.2 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 7_10_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.10.2 + - 7_10_2-check: | + cd example.org + cabal check + - 7_10_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_10_2-build: | + cd example.org + cabal build all + - 7_10_2-test: | + cd example.org + cabal test all --enable-tests + - 7_10_2-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 7.10.3 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--ghc-head' 'sourcehut' 'empty-line.project' +# +# 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 +# +# REGENDATA ["--ghc-head","sourcehut","empty-line.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-7.10.3 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 7_10_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.10.3 + - 7_10_3-check: | + cd example.org + cabal check + - 7_10_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_10_3-build: | + cd example.org + cabal build all + - 7_10_3-test: | + cd example.org + cabal test all --enable-tests + - 7_10_3-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 7.8.1 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--ghc-head' 'sourcehut' 'empty-line.project' +# +# 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 +# +# REGENDATA ["--ghc-head","sourcehut","empty-line.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-7.8.1 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 7_8_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.8.1 + - 7_8_1-check: | + cd example.org + cabal check + - 7_8_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_8_1-build: | + cd example.org + cabal build all + - 7_8_1-test: | + cd example.org + cabal test all --enable-tests + - 7_8_1-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 7.8.2 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--ghc-head' 'sourcehut' 'empty-line.project' +# +# 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 +# +# REGENDATA ["--ghc-head","sourcehut","empty-line.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-7.8.2 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 7_8_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.8.2 + - 7_8_2-check: | + cd example.org + cabal check + - 7_8_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_8_2-build: | + cd example.org + cabal build all + - 7_8_2-test: | + cd example.org + cabal test all --enable-tests + - 7_8_2-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 7.8.3 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--ghc-head' 'sourcehut' 'empty-line.project' +# +# 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 +# +# REGENDATA ["--ghc-head","sourcehut","empty-line.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-7.8.3 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 7_8_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.8.3 + - 7_8_3-check: | + cd example.org + cabal check + - 7_8_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_8_3-build: | + cd example.org + cabal build all + - 7_8_3-test: | + cd example.org + cabal test all --enable-tests + - 7_8_3-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 7.8.4 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--ghc-head' 'sourcehut' 'empty-line.project' +# +# 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 +# +# REGENDATA ["--ghc-head","sourcehut","empty-line.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-7.8.4 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 7_8_4-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.8.4 + - 7_8_4-check: | + cd example.org + cabal check + - 7_8_4-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_8_4-build: | + cd example.org + cabal build all + - 7_8_4-test: | + cd example.org + cabal test all --enable-tests + - 7_8_4-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.0.1 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--ghc-head' 'sourcehut' 'empty-line.project' +# +# 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 +# +# REGENDATA ["--ghc-head","sourcehut","empty-line.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.0.1 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_0_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.0.1 + - 8_0_1-check: | + cd example.org + cabal check + - 8_0_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_0_1-build: | + cd example.org + cabal build all + - 8_0_1-test: | + cd example.org + cabal test all --enable-tests + - 8_0_1-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.0.2 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--ghc-head' 'sourcehut' 'empty-line.project' +# +# 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 +# +# REGENDATA ["--ghc-head","sourcehut","empty-line.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.0.2 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_0_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.0.2 + - 8_0_2-check: | + cd example.org + cabal check + - 8_0_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_0_2-build: | + cd example.org + cabal build all + - 8_0_2-test: | + cd example.org + cabal test all --enable-tests + - 8_0_2-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.10.1 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--ghc-head' 'sourcehut' 'empty-line.project' +# +# 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 +# +# REGENDATA ["--ghc-head","sourcehut","empty-line.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.10.1 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_10_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.1 + - 8_10_1-check: | + cd example.org + cabal check + - 8_10_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_1-build: | + cd example.org + cabal build all + - 8_10_1-test: | + cd example.org + cabal test all --enable-tests + - 8_10_1-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.10.2 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--ghc-head' 'sourcehut' 'empty-line.project' +# +# 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 +# +# REGENDATA ["--ghc-head","sourcehut","empty-line.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.10.2 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_10_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.2 + - 8_10_2-check: | + cd example.org + cabal check + - 8_10_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_2-build: | + cd example.org + cabal build all + - 8_10_2-test: | + cd example.org + cabal test all --enable-tests + - 8_10_2-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.10.3 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--ghc-head' 'sourcehut' 'empty-line.project' +# +# 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 +# +# REGENDATA ["--ghc-head","sourcehut","empty-line.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.10.3 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_10_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.3 + - 8_10_3-check: | + cd example.org + cabal check + - 8_10_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_3-build: | + cd example.org + cabal build all + - 8_10_3-test: | + cd example.org + cabal test all --enable-tests + - 8_10_3-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.10.4 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--ghc-head' 'sourcehut' 'empty-line.project' +# +# 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 +# +# REGENDATA ["--ghc-head","sourcehut","empty-line.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.10.4 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_10_4-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.4 + - 8_10_4-check: | + cd example.org + cabal check + - 8_10_4-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_4-build: | + cd example.org + cabal build all + - 8_10_4-test: | + cd example.org + cabal test all --enable-tests + - 8_10_4-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.10.5 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--ghc-head' 'sourcehut' 'empty-line.project' +# +# 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 +# +# REGENDATA ["--ghc-head","sourcehut","empty-line.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.10.5 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_10_5-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.5 + - 8_10_5-check: | + cd example.org + cabal check + - 8_10_5-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_5-build: | + cd example.org + cabal build all + - 8_10_5-test: | + cd example.org + cabal test all --enable-tests + - 8_10_5-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.10.6 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--ghc-head' 'sourcehut' 'empty-line.project' +# +# 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 +# +# REGENDATA ["--ghc-head","sourcehut","empty-line.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.10.6 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_10_6-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.6 + - 8_10_6-check: | + cd example.org + cabal check + - 8_10_6-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_6-build: | + cd example.org + cabal build all + - 8_10_6-test: | + cd example.org + cabal test all --enable-tests + - 8_10_6-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.10.7 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--ghc-head' 'sourcehut' 'empty-line.project' +# +# 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 +# +# REGENDATA ["--ghc-head","sourcehut","empty-line.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.10.7 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_10_7-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.7 + - 8_10_7-check: | + cd example.org + cabal check + - 8_10_7-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_7-build: | + cd example.org + cabal build all + - 8_10_7-test: | + cd example.org + cabal test all --enable-tests + - 8_10_7-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.2.1 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--ghc-head' 'sourcehut' 'empty-line.project' +# +# 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 +# +# REGENDATA ["--ghc-head","sourcehut","empty-line.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.2.1 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_2_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.2.1 + - 8_2_1-check: | + cd example.org + cabal check + - 8_2_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_2_1-build: | + cd example.org + cabal build all + - 8_2_1-test: | + cd example.org + cabal test all --enable-tests + - 8_2_1-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.2.2 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--ghc-head' 'sourcehut' 'empty-line.project' +# +# 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 +# +# REGENDATA ["--ghc-head","sourcehut","empty-line.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.2.2 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_2_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.2.2 + - 8_2_2-check: | + cd example.org + cabal check + - 8_2_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_2_2-build: | + cd example.org + cabal build all + - 8_2_2-test: | + cd example.org + cabal test all --enable-tests + - 8_2_2-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.4.1 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--ghc-head' 'sourcehut' 'empty-line.project' +# +# 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 +# +# REGENDATA ["--ghc-head","sourcehut","empty-line.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.4.1 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_4_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.4.1 + - 8_4_1-check: | + cd example.org + cabal check + - 8_4_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_4_1-build: | + cd example.org + cabal build all + - 8_4_1-test: | + cd example.org + cabal test all --enable-tests + - 8_4_1-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.4.2 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--ghc-head' 'sourcehut' 'empty-line.project' +# +# 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 +# +# REGENDATA ["--ghc-head","sourcehut","empty-line.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.4.2 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_4_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.4.2 + - 8_4_2-check: | + cd example.org + cabal check + - 8_4_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_4_2-build: | + cd example.org + cabal build all + - 8_4_2-test: | + cd example.org + cabal test all --enable-tests + - 8_4_2-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.4.3 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--ghc-head' 'sourcehut' 'empty-line.project' +# +# 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 +# +# REGENDATA ["--ghc-head","sourcehut","empty-line.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.4.3 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_4_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.4.3 + - 8_4_3-check: | + cd example.org + cabal check + - 8_4_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_4_3-build: | + cd example.org + cabal build all + - 8_4_3-test: | + cd example.org + cabal test all --enable-tests + - 8_4_3-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.4.4 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--ghc-head' 'sourcehut' 'empty-line.project' +# +# 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 +# +# REGENDATA ["--ghc-head","sourcehut","empty-line.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.4.4 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_4_4-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.4.4 + - 8_4_4-check: | + cd example.org + cabal check + - 8_4_4-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_4_4-build: | + cd example.org + cabal build all + - 8_4_4-test: | + cd example.org + cabal test all --enable-tests + - 8_4_4-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.6.1 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--ghc-head' 'sourcehut' 'empty-line.project' +# +# 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 +# +# REGENDATA ["--ghc-head","sourcehut","empty-line.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.6.1 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_6_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.6.1 + - 8_6_1-check: | + cd example.org + cabal check + - 8_6_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_6_1-build: | + cd example.org + cabal build all + - 8_6_1-test: | + cd example.org + cabal test all --enable-tests + - 8_6_1-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.6.2 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--ghc-head' 'sourcehut' 'empty-line.project' +# +# 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 +# +# REGENDATA ["--ghc-head","sourcehut","empty-line.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.6.2 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_6_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.6.2 + - 8_6_2-check: | + cd example.org + cabal check + - 8_6_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_6_2-build: | + cd example.org + cabal build all + - 8_6_2-test: | + cd example.org + cabal test all --enable-tests + - 8_6_2-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.6.3 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--ghc-head' 'sourcehut' 'empty-line.project' +# +# 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 +# +# REGENDATA ["--ghc-head","sourcehut","empty-line.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.6.3 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_6_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.6.3 + - 8_6_3-check: | + cd example.org + cabal check + - 8_6_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_6_3-build: | + cd example.org + cabal build all + - 8_6_3-test: | + cd example.org + cabal test all --enable-tests + - 8_6_3-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.6.4 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--ghc-head' 'sourcehut' 'empty-line.project' +# +# 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 +# +# REGENDATA ["--ghc-head","sourcehut","empty-line.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.6.4 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_6_4-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.6.4 + - 8_6_4-check: | + cd example.org + cabal check + - 8_6_4-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_6_4-build: | + cd example.org + cabal build all + - 8_6_4-test: | + cd example.org + cabal test all --enable-tests + - 8_6_4-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.6.5 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--ghc-head' 'sourcehut' 'empty-line.project' +# +# 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 +# +# REGENDATA ["--ghc-head","sourcehut","empty-line.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.6.5 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_6_5-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.6.5 + - 8_6_5-check: | + cd example.org + cabal check + - 8_6_5-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_6_5-build: | + cd example.org + cabal build all + - 8_6_5-test: | + cd example.org + cabal test all --enable-tests + - 8_6_5-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.8.1 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--ghc-head' 'sourcehut' 'empty-line.project' +# +# 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 +# +# REGENDATA ["--ghc-head","sourcehut","empty-line.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.8.1 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_8_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.8.1 + - 8_8_1-check: | + cd example.org + cabal check + - 8_8_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_8_1-build: | + cd example.org + cabal build all + - 8_8_1-test: | + cd example.org + cabal test all --enable-tests + - 8_8_1-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.8.2 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--ghc-head' 'sourcehut' 'empty-line.project' +# +# 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 +# +# REGENDATA ["--ghc-head","sourcehut","empty-line.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.8.2 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_8_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.8.2 + - 8_8_2-check: | + cd example.org + cabal check + - 8_8_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_8_2-build: | + cd example.org + cabal build all + - 8_8_2-test: | + cd example.org + cabal test all --enable-tests + - 8_8_2-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.8.3 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--ghc-head' 'sourcehut' 'empty-line.project' +# +# 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 +# +# REGENDATA ["--ghc-head","sourcehut","empty-line.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.8.3 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_8_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.8.3 + - 8_8_3-check: | + cd example.org + cabal check + - 8_8_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_8_3-build: | + cd example.org + cabal build all + - 8_8_3-test: | + cd example.org + cabal test all --enable-tests + - 8_8_3-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.8.4 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--ghc-head' 'sourcehut' 'empty-line.project' +# +# 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 +# +# REGENDATA ["--ghc-head","sourcehut","empty-line.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.8.4 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_8_4-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.8.4 + - 8_8_4-check: | + cd example.org + cabal check + - 8_8_4-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_8_4-build: | + cd example.org + cabal build all + - 8_8_4-test: | + cd example.org + cabal test all --enable-tests + - 8_8_4-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: ghc-head +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--ghc-head' 'sourcehut' 'empty-line.project' +# +# 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 +# +# REGENDATA ["--ghc-head","sourcehut","empty-line.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-head +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - ghc-head-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-head + - ghc-head-check: | + cd example.org + cabal check + - ghc-head-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - ghc-head-build: | + cd example.org + cabal build all + - ghc-head-test: | + cd example.org + cabal test all --enable-tests + - ghc-head-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com diff --git a/fixtures/enabled-jobs.sourcehut b/fixtures/enabled-jobs.sourcehut new file mode 100644 index 00000000..942e6428 --- /dev/null +++ b/fixtures/enabled-jobs.sourcehut @@ -0,0 +1,572 @@ +# SUCCESS +# *INFO* Generating Sourcehut config for testing for GHC versions: 8.0.1 8.0.2 8.2.1 8.2.2 8.4.1 8.4.2 8.4.3 8.4.4 8.6.1 8.6.2 8.6.3 8.6.4 8.6.5 8.8.1 8.8.2 8.8.3 8.8.4 8.10.1 8.10.2 8.10.3 8.10.4 8.10.5 8.10.6 8.10.7 9.0.1 9.2.1 ghcjs-8.4 +# manifest name: all +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--enabled-jobs=>=8' 'sourcehut' 'enabled-jobs.project' +# +# 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 +# +# REGENDATA ["--enabled-jobs=>=8","sourcehut","enabled-jobs.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.0.1 + - ghc-8.0.2 + - ghc-8.2.1 + - ghc-8.2.2 + - ghc-8.4.1 + - ghc-8.4.2 + - ghc-8.4.3 + - ghc-8.4.4 + - ghc-8.6.1 + - ghc-8.6.2 + - ghc-8.6.3 + - ghc-8.6.4 + - ghc-8.6.5 + - ghc-8.8.1 + - ghc-8.8.2 + - ghc-8.8.3 + - ghc-8.8.4 + - ghc-8.10.1 + - ghc-8.10.2 + - ghc-8.10.3 + - ghc-8.10.4 + - ghc-8.10.5 + - ghc-8.10.6 + - ghc-8.10.7 + - ghc-9.0.1 + - ghc-9.2.1 + - ghcjs-8.4 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_0_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.0.1 + - 8_0_1-check: | + cd example.org + cabal check + - 8_0_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_0_1-build: | + cd example.org + cabal build all + - 8_0_1-test: | + cd example.org + cabal test all --enable-tests + - 8_0_1-haddock: | + cd example.org + cabal haddock all + - 8_0_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.0.2 + - 8_0_2-check: | + cd example.org + cabal check + - 8_0_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_0_2-build: | + cd example.org + cabal build all + - 8_0_2-test: | + cd example.org + cabal test all --enable-tests + - 8_0_2-haddock: | + cd example.org + cabal haddock all + - 8_2_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.2.1 + - 8_2_1-check: | + cd example.org + cabal check + - 8_2_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_2_1-build: | + cd example.org + cabal build all + - 8_2_1-test: | + cd example.org + cabal test all --enable-tests + - 8_2_1-haddock: | + cd example.org + cabal haddock all + - 8_2_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.2.2 + - 8_2_2-check: | + cd example.org + cabal check + - 8_2_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_2_2-build: | + cd example.org + cabal build all + - 8_2_2-test: | + cd example.org + cabal test all --enable-tests + - 8_2_2-haddock: | + cd example.org + cabal haddock all + - 8_4_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.4.1 + - 8_4_1-check: | + cd example.org + cabal check + - 8_4_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_4_1-build: | + cd example.org + cabal build all + - 8_4_1-test: | + cd example.org + cabal test all --enable-tests + - 8_4_1-haddock: | + cd example.org + cabal haddock all + - 8_4_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.4.2 + - 8_4_2-check: | + cd example.org + cabal check + - 8_4_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_4_2-build: | + cd example.org + cabal build all + - 8_4_2-test: | + cd example.org + cabal test all --enable-tests + - 8_4_2-haddock: | + cd example.org + cabal haddock all + - 8_4_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.4.3 + - 8_4_3-check: | + cd example.org + cabal check + - 8_4_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_4_3-build: | + cd example.org + cabal build all + - 8_4_3-test: | + cd example.org + cabal test all --enable-tests + - 8_4_3-haddock: | + cd example.org + cabal haddock all + - 8_4_4-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.4.4 + - 8_4_4-check: | + cd example.org + cabal check + - 8_4_4-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_4_4-build: | + cd example.org + cabal build all + - 8_4_4-test: | + cd example.org + cabal test all --enable-tests + - 8_4_4-haddock: | + cd example.org + cabal haddock all + - 8_6_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.6.1 + - 8_6_1-check: | + cd example.org + cabal check + - 8_6_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_6_1-build: | + cd example.org + cabal build all + - 8_6_1-test: | + cd example.org + cabal test all --enable-tests + - 8_6_1-haddock: | + cd example.org + cabal haddock all + - 8_6_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.6.2 + - 8_6_2-check: | + cd example.org + cabal check + - 8_6_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_6_2-build: | + cd example.org + cabal build all + - 8_6_2-test: | + cd example.org + cabal test all --enable-tests + - 8_6_2-haddock: | + cd example.org + cabal haddock all + - 8_6_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.6.3 + - 8_6_3-check: | + cd example.org + cabal check + - 8_6_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_6_3-build: | + cd example.org + cabal build all + - 8_6_3-test: | + cd example.org + cabal test all --enable-tests + - 8_6_3-haddock: | + cd example.org + cabal haddock all + - 8_6_4-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.6.4 + - 8_6_4-check: | + cd example.org + cabal check + - 8_6_4-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_6_4-build: | + cd example.org + cabal build all + - 8_6_4-test: | + cd example.org + cabal test all --enable-tests + - 8_6_4-haddock: | + cd example.org + cabal haddock all + - 8_6_5-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.6.5 + - 8_6_5-check: | + cd example.org + cabal check + - 8_6_5-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_6_5-build: | + cd example.org + cabal build all + - 8_6_5-test: | + cd example.org + cabal test all --enable-tests + - 8_6_5-haddock: | + cd example.org + cabal haddock all + - 8_8_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.8.1 + - 8_8_1-check: | + cd example.org + cabal check + - 8_8_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_8_1-build: | + cd example.org + cabal build all + - 8_8_1-test: | + cd example.org + cabal test all --enable-tests + - 8_8_1-haddock: | + cd example.org + cabal haddock all + - 8_8_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.8.2 + - 8_8_2-check: | + cd example.org + cabal check + - 8_8_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_8_2-build: | + cd example.org + cabal build all + - 8_8_2-test: | + cd example.org + cabal test all --enable-tests + - 8_8_2-haddock: | + cd example.org + cabal haddock all + - 8_8_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.8.3 + - 8_8_3-check: | + cd example.org + cabal check + - 8_8_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_8_3-build: | + cd example.org + cabal build all + - 8_8_3-test: | + cd example.org + cabal test all --enable-tests + - 8_8_3-haddock: | + cd example.org + cabal haddock all + - 8_8_4-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.8.4 + - 8_8_4-check: | + cd example.org + cabal check + - 8_8_4-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_8_4-build: | + cd example.org + cabal build all + - 8_8_4-test: | + cd example.org + cabal test all --enable-tests + - 8_8_4-haddock: | + cd example.org + cabal haddock all + - 8_10_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.1 + - 8_10_1-check: | + cd example.org + cabal check + - 8_10_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_1-build: | + cd example.org + cabal build all + - 8_10_1-test: | + cd example.org + cabal test all --enable-tests + - 8_10_1-haddock: | + cd example.org + cabal haddock all + - 8_10_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.2 + - 8_10_2-check: | + cd example.org + cabal check + - 8_10_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_2-build: | + cd example.org + cabal build all + - 8_10_2-test: | + cd example.org + cabal test all --enable-tests + - 8_10_2-haddock: | + cd example.org + cabal haddock all + - 8_10_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.3 + - 8_10_3-check: | + cd example.org + cabal check + - 8_10_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_3-build: | + cd example.org + cabal build all + - 8_10_3-test: | + cd example.org + cabal test all --enable-tests + - 8_10_3-haddock: | + cd example.org + cabal haddock all + - 8_10_4-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.4 + - 8_10_4-check: | + cd example.org + cabal check + - 8_10_4-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_4-build: | + cd example.org + cabal build all + - 8_10_4-test: | + cd example.org + cabal test all --enable-tests + - 8_10_4-haddock: | + cd example.org + cabal haddock all + - 8_10_5-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.5 + - 8_10_5-check: | + cd example.org + cabal check + - 8_10_5-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_5-build: | + cd example.org + cabal build all + - 8_10_5-test: | + cd example.org + cabal test all --enable-tests + - 8_10_5-haddock: | + cd example.org + cabal haddock all + - 8_10_6-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.6 + - 8_10_6-check: | + cd example.org + cabal check + - 8_10_6-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_6-build: | + cd example.org + cabal build all + - 8_10_6-test: | + cd example.org + cabal test all --enable-tests + - 8_10_6-haddock: | + cd example.org + cabal haddock all + - 8_10_7-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.7 + - 8_10_7-check: | + cd example.org + cabal check + - 8_10_7-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_7-build: | + cd example.org + cabal build all + - 8_10_7-test: | + cd example.org + cabal test all --enable-tests + - 8_10_7-haddock: | + cd example.org + cabal haddock all + - 9_0_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-9.0.1 + - 9_0_1-check: | + cd example.org + cabal check + - 9_0_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 9_0_1-build: | + cd example.org + cabal build all + - 9_0_1-test: | + cd example.org + cabal test all --enable-tests + - 9_0_1-haddock: | + cd example.org + cabal haddock all + - 9_2_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-9.2.1 + - 9_2_1-check: | + cd example.org + cabal check + - 9_2_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 9_2_1-build: | + cd example.org + cabal build all + - 9_2_1-test: | + cd example.org + cabal test all --enable-tests + - 9_2_1-haddock: | + cd example.org + cabal haddock all + - ghcjs-8_4-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghcjs-8.4 + - ghcjs-8_4-check: | + cd example.org + cabal check + - ghcjs-8_4-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - ghcjs-8_4-build: | + cd example.org + cabal build all + - ghcjs-8_4-test: | + cd example.org + cabal test all --enable-tests + - ghcjs-8_4-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: Oleg Grenrus diff --git a/fixtures/enabled-jobs.sourcehut-parallel b/fixtures/enabled-jobs.sourcehut-parallel new file mode 100644 index 00000000..856792cc --- /dev/null +++ b/fixtures/enabled-jobs.sourcehut-parallel @@ -0,0 +1,1352 @@ +# SUCCESS +# *INFO* Generating Sourcehut config for testing for GHC versions: 8.0.1 8.0.2 8.2.1 8.2.2 8.4.1 8.4.2 8.4.3 8.4.4 8.6.1 8.6.2 8.6.3 8.6.4 8.6.5 8.8.1 8.8.2 8.8.3 8.8.4 8.10.1 8.10.2 8.10.3 8.10.4 8.10.5 8.10.6 8.10.7 9.0.1 9.2.1 ghcjs-8.4 +# manifest name: 8.0.1 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--enabled-jobs=>=8' 'sourcehut' 'enabled-jobs.project' +# +# 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 +# +# REGENDATA ["--enabled-jobs=>=8","sourcehut","enabled-jobs.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.0.1 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_0_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.0.1 + - 8_0_1-check: | + cd example.org + cabal check + - 8_0_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_0_1-build: | + cd example.org + cabal build all + - 8_0_1-test: | + cd example.org + cabal test all --enable-tests + - 8_0_1-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: Oleg Grenrus +# manifest name: 8.0.2 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--enabled-jobs=>=8' 'sourcehut' 'enabled-jobs.project' +# +# 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 +# +# REGENDATA ["--enabled-jobs=>=8","sourcehut","enabled-jobs.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.0.2 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_0_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.0.2 + - 8_0_2-check: | + cd example.org + cabal check + - 8_0_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_0_2-build: | + cd example.org + cabal build all + - 8_0_2-test: | + cd example.org + cabal test all --enable-tests + - 8_0_2-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: Oleg Grenrus +# manifest name: 8.10.1 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--enabled-jobs=>=8' 'sourcehut' 'enabled-jobs.project' +# +# 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 +# +# REGENDATA ["--enabled-jobs=>=8","sourcehut","enabled-jobs.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.10.1 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_10_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.1 + - 8_10_1-check: | + cd example.org + cabal check + - 8_10_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_1-build: | + cd example.org + cabal build all + - 8_10_1-test: | + cd example.org + cabal test all --enable-tests + - 8_10_1-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: Oleg Grenrus +# manifest name: 8.10.2 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--enabled-jobs=>=8' 'sourcehut' 'enabled-jobs.project' +# +# 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 +# +# REGENDATA ["--enabled-jobs=>=8","sourcehut","enabled-jobs.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.10.2 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_10_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.2 + - 8_10_2-check: | + cd example.org + cabal check + - 8_10_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_2-build: | + cd example.org + cabal build all + - 8_10_2-test: | + cd example.org + cabal test all --enable-tests + - 8_10_2-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: Oleg Grenrus +# manifest name: 8.10.3 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--enabled-jobs=>=8' 'sourcehut' 'enabled-jobs.project' +# +# 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 +# +# REGENDATA ["--enabled-jobs=>=8","sourcehut","enabled-jobs.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.10.3 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_10_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.3 + - 8_10_3-check: | + cd example.org + cabal check + - 8_10_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_3-build: | + cd example.org + cabal build all + - 8_10_3-test: | + cd example.org + cabal test all --enable-tests + - 8_10_3-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: Oleg Grenrus +# manifest name: 8.10.4 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--enabled-jobs=>=8' 'sourcehut' 'enabled-jobs.project' +# +# 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 +# +# REGENDATA ["--enabled-jobs=>=8","sourcehut","enabled-jobs.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.10.4 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_10_4-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.4 + - 8_10_4-check: | + cd example.org + cabal check + - 8_10_4-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_4-build: | + cd example.org + cabal build all + - 8_10_4-test: | + cd example.org + cabal test all --enable-tests + - 8_10_4-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: Oleg Grenrus +# manifest name: 8.10.5 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--enabled-jobs=>=8' 'sourcehut' 'enabled-jobs.project' +# +# 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 +# +# REGENDATA ["--enabled-jobs=>=8","sourcehut","enabled-jobs.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.10.5 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_10_5-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.5 + - 8_10_5-check: | + cd example.org + cabal check + - 8_10_5-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_5-build: | + cd example.org + cabal build all + - 8_10_5-test: | + cd example.org + cabal test all --enable-tests + - 8_10_5-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: Oleg Grenrus +# manifest name: 8.10.6 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--enabled-jobs=>=8' 'sourcehut' 'enabled-jobs.project' +# +# 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 +# +# REGENDATA ["--enabled-jobs=>=8","sourcehut","enabled-jobs.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.10.6 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_10_6-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.6 + - 8_10_6-check: | + cd example.org + cabal check + - 8_10_6-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_6-build: | + cd example.org + cabal build all + - 8_10_6-test: | + cd example.org + cabal test all --enable-tests + - 8_10_6-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: Oleg Grenrus +# manifest name: 8.10.7 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--enabled-jobs=>=8' 'sourcehut' 'enabled-jobs.project' +# +# 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 +# +# REGENDATA ["--enabled-jobs=>=8","sourcehut","enabled-jobs.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.10.7 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_10_7-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.7 + - 8_10_7-check: | + cd example.org + cabal check + - 8_10_7-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_7-build: | + cd example.org + cabal build all + - 8_10_7-test: | + cd example.org + cabal test all --enable-tests + - 8_10_7-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: Oleg Grenrus +# manifest name: 8.2.1 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--enabled-jobs=>=8' 'sourcehut' 'enabled-jobs.project' +# +# 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 +# +# REGENDATA ["--enabled-jobs=>=8","sourcehut","enabled-jobs.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.2.1 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_2_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.2.1 + - 8_2_1-check: | + cd example.org + cabal check + - 8_2_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_2_1-build: | + cd example.org + cabal build all + - 8_2_1-test: | + cd example.org + cabal test all --enable-tests + - 8_2_1-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: Oleg Grenrus +# manifest name: 8.2.2 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--enabled-jobs=>=8' 'sourcehut' 'enabled-jobs.project' +# +# 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 +# +# REGENDATA ["--enabled-jobs=>=8","sourcehut","enabled-jobs.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.2.2 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_2_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.2.2 + - 8_2_2-check: | + cd example.org + cabal check + - 8_2_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_2_2-build: | + cd example.org + cabal build all + - 8_2_2-test: | + cd example.org + cabal test all --enable-tests + - 8_2_2-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: Oleg Grenrus +# manifest name: 8.4.1 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--enabled-jobs=>=8' 'sourcehut' 'enabled-jobs.project' +# +# 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 +# +# REGENDATA ["--enabled-jobs=>=8","sourcehut","enabled-jobs.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.4.1 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_4_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.4.1 + - 8_4_1-check: | + cd example.org + cabal check + - 8_4_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_4_1-build: | + cd example.org + cabal build all + - 8_4_1-test: | + cd example.org + cabal test all --enable-tests + - 8_4_1-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: Oleg Grenrus +# manifest name: 8.4.2 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--enabled-jobs=>=8' 'sourcehut' 'enabled-jobs.project' +# +# 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 +# +# REGENDATA ["--enabled-jobs=>=8","sourcehut","enabled-jobs.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.4.2 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_4_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.4.2 + - 8_4_2-check: | + cd example.org + cabal check + - 8_4_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_4_2-build: | + cd example.org + cabal build all + - 8_4_2-test: | + cd example.org + cabal test all --enable-tests + - 8_4_2-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: Oleg Grenrus +# manifest name: 8.4.3 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--enabled-jobs=>=8' 'sourcehut' 'enabled-jobs.project' +# +# 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 +# +# REGENDATA ["--enabled-jobs=>=8","sourcehut","enabled-jobs.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.4.3 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_4_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.4.3 + - 8_4_3-check: | + cd example.org + cabal check + - 8_4_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_4_3-build: | + cd example.org + cabal build all + - 8_4_3-test: | + cd example.org + cabal test all --enable-tests + - 8_4_3-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: Oleg Grenrus +# manifest name: 8.4.4 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--enabled-jobs=>=8' 'sourcehut' 'enabled-jobs.project' +# +# 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 +# +# REGENDATA ["--enabled-jobs=>=8","sourcehut","enabled-jobs.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.4.4 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_4_4-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.4.4 + - 8_4_4-check: | + cd example.org + cabal check + - 8_4_4-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_4_4-build: | + cd example.org + cabal build all + - 8_4_4-test: | + cd example.org + cabal test all --enable-tests + - 8_4_4-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: Oleg Grenrus +# manifest name: 8.6.1 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--enabled-jobs=>=8' 'sourcehut' 'enabled-jobs.project' +# +# 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 +# +# REGENDATA ["--enabled-jobs=>=8","sourcehut","enabled-jobs.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.6.1 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_6_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.6.1 + - 8_6_1-check: | + cd example.org + cabal check + - 8_6_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_6_1-build: | + cd example.org + cabal build all + - 8_6_1-test: | + cd example.org + cabal test all --enable-tests + - 8_6_1-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: Oleg Grenrus +# manifest name: 8.6.2 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--enabled-jobs=>=8' 'sourcehut' 'enabled-jobs.project' +# +# 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 +# +# REGENDATA ["--enabled-jobs=>=8","sourcehut","enabled-jobs.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.6.2 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_6_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.6.2 + - 8_6_2-check: | + cd example.org + cabal check + - 8_6_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_6_2-build: | + cd example.org + cabal build all + - 8_6_2-test: | + cd example.org + cabal test all --enable-tests + - 8_6_2-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: Oleg Grenrus +# manifest name: 8.6.3 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--enabled-jobs=>=8' 'sourcehut' 'enabled-jobs.project' +# +# 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 +# +# REGENDATA ["--enabled-jobs=>=8","sourcehut","enabled-jobs.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.6.3 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_6_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.6.3 + - 8_6_3-check: | + cd example.org + cabal check + - 8_6_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_6_3-build: | + cd example.org + cabal build all + - 8_6_3-test: | + cd example.org + cabal test all --enable-tests + - 8_6_3-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: Oleg Grenrus +# manifest name: 8.6.4 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--enabled-jobs=>=8' 'sourcehut' 'enabled-jobs.project' +# +# 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 +# +# REGENDATA ["--enabled-jobs=>=8","sourcehut","enabled-jobs.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.6.4 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_6_4-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.6.4 + - 8_6_4-check: | + cd example.org + cabal check + - 8_6_4-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_6_4-build: | + cd example.org + cabal build all + - 8_6_4-test: | + cd example.org + cabal test all --enable-tests + - 8_6_4-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: Oleg Grenrus +# manifest name: 8.6.5 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--enabled-jobs=>=8' 'sourcehut' 'enabled-jobs.project' +# +# 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 +# +# REGENDATA ["--enabled-jobs=>=8","sourcehut","enabled-jobs.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.6.5 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_6_5-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.6.5 + - 8_6_5-check: | + cd example.org + cabal check + - 8_6_5-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_6_5-build: | + cd example.org + cabal build all + - 8_6_5-test: | + cd example.org + cabal test all --enable-tests + - 8_6_5-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: Oleg Grenrus +# manifest name: 8.8.1 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--enabled-jobs=>=8' 'sourcehut' 'enabled-jobs.project' +# +# 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 +# +# REGENDATA ["--enabled-jobs=>=8","sourcehut","enabled-jobs.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.8.1 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_8_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.8.1 + - 8_8_1-check: | + cd example.org + cabal check + - 8_8_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_8_1-build: | + cd example.org + cabal build all + - 8_8_1-test: | + cd example.org + cabal test all --enable-tests + - 8_8_1-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: Oleg Grenrus +# manifest name: 8.8.2 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--enabled-jobs=>=8' 'sourcehut' 'enabled-jobs.project' +# +# 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 +# +# REGENDATA ["--enabled-jobs=>=8","sourcehut","enabled-jobs.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.8.2 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_8_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.8.2 + - 8_8_2-check: | + cd example.org + cabal check + - 8_8_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_8_2-build: | + cd example.org + cabal build all + - 8_8_2-test: | + cd example.org + cabal test all --enable-tests + - 8_8_2-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: Oleg Grenrus +# manifest name: 8.8.3 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--enabled-jobs=>=8' 'sourcehut' 'enabled-jobs.project' +# +# 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 +# +# REGENDATA ["--enabled-jobs=>=8","sourcehut","enabled-jobs.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.8.3 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_8_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.8.3 + - 8_8_3-check: | + cd example.org + cabal check + - 8_8_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_8_3-build: | + cd example.org + cabal build all + - 8_8_3-test: | + cd example.org + cabal test all --enable-tests + - 8_8_3-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: Oleg Grenrus +# manifest name: 8.8.4 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--enabled-jobs=>=8' 'sourcehut' 'enabled-jobs.project' +# +# 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 +# +# REGENDATA ["--enabled-jobs=>=8","sourcehut","enabled-jobs.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.8.4 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_8_4-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.8.4 + - 8_8_4-check: | + cd example.org + cabal check + - 8_8_4-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_8_4-build: | + cd example.org + cabal build all + - 8_8_4-test: | + cd example.org + cabal test all --enable-tests + - 8_8_4-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: Oleg Grenrus +# manifest name: 9.0.1 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--enabled-jobs=>=8' 'sourcehut' 'enabled-jobs.project' +# +# 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 +# +# REGENDATA ["--enabled-jobs=>=8","sourcehut","enabled-jobs.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-9.0.1 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 9_0_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-9.0.1 + - 9_0_1-check: | + cd example.org + cabal check + - 9_0_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 9_0_1-build: | + cd example.org + cabal build all + - 9_0_1-test: | + cd example.org + cabal test all --enable-tests + - 9_0_1-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: Oleg Grenrus +# manifest name: 9.2.1 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--enabled-jobs=>=8' 'sourcehut' 'enabled-jobs.project' +# +# 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 +# +# REGENDATA ["--enabled-jobs=>=8","sourcehut","enabled-jobs.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-9.2.1 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 9_2_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-9.2.1 + - 9_2_1-check: | + cd example.org + cabal check + - 9_2_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 9_2_1-build: | + cd example.org + cabal build all + - 9_2_1-test: | + cd example.org + cabal test all --enable-tests + - 9_2_1-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: Oleg Grenrus +# manifest name: ghcjs-8.4 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--enabled-jobs=>=8' 'sourcehut' 'enabled-jobs.project' +# +# 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 +# +# REGENDATA ["--enabled-jobs=>=8","sourcehut","enabled-jobs.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghcjs-8.4 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - ghcjs-8_4-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghcjs-8.4 + - ghcjs-8_4-check: | + cd example.org + cabal check + - ghcjs-8_4-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - ghcjs-8_4-build: | + cd example.org + cabal build all + - ghcjs-8_4-test: | + cd example.org + cabal test all --enable-tests + - ghcjs-8_4-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: Oleg Grenrus diff --git a/fixtures/fail-versions.sourcehut b/fixtures/fail-versions.sourcehut new file mode 100644 index 00000000..0e629b61 --- /dev/null +++ b/fixtures/fail-versions.sourcehut @@ -0,0 +1,3 @@ +# FAILURE +# *ERROR* servant-client-core is missing tested-with annotations for: ghc-7.8.1,ghc-7.8.2,ghc-7.8.3,ghc-7.8.4 +# *ERROR* servant-foreign is missing tested-with annotations for: ghc-7.8.1,ghc-7.8.2,ghc-7.8.3,ghc-7.8.4 diff --git a/fixtures/fail-versions.sourcehut-parallel b/fixtures/fail-versions.sourcehut-parallel new file mode 100644 index 00000000..0e629b61 --- /dev/null +++ b/fixtures/fail-versions.sourcehut-parallel @@ -0,0 +1,3 @@ +# FAILURE +# *ERROR* servant-client-core is missing tested-with annotations for: ghc-7.8.1,ghc-7.8.2,ghc-7.8.3,ghc-7.8.4 +# *ERROR* servant-foreign is missing tested-with annotations for: ghc-7.8.1,ghc-7.8.2,ghc-7.8.3,ghc-7.8.4 diff --git a/fixtures/irc-channels.sourcehut b/fixtures/irc-channels.sourcehut new file mode 100644 index 00000000..74c0ccff --- /dev/null +++ b/fixtures/irc-channels.sourcehut @@ -0,0 +1,652 @@ +# SUCCESS +# *INFO* Generating Sourcehut config for testing for GHC versions: 7.8.1 7.8.2 7.8.3 7.8.4 7.10.1 7.10.2 7.10.3 8.0.1 8.0.2 8.2.1 8.2.2 8.4.1 8.4.2 8.4.3 8.4.4 8.6.1 8.6.2 8.6.3 8.6.4 8.6.5 8.8.1 8.8.2 8.8.3 8.8.4 8.10.1 8.10.2 8.10.3 8.10.4 8.10.5 8.10.6 8.10.7 +# manifest name: all +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--irc-channels=irc.libera.chat#mychannel' 'sourcehut' 'irc-channels.project' +# +# 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 +# +# REGENDATA ["--irc-channels=irc.libera.chat#mychannel","sourcehut","irc-channels.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-7.8.1 + - ghc-7.8.2 + - ghc-7.8.3 + - ghc-7.8.4 + - ghc-7.10.1 + - ghc-7.10.2 + - ghc-7.10.3 + - ghc-8.0.1 + - ghc-8.0.2 + - ghc-8.2.1 + - ghc-8.2.2 + - ghc-8.4.1 + - ghc-8.4.2 + - ghc-8.4.3 + - ghc-8.4.4 + - ghc-8.6.1 + - ghc-8.6.2 + - ghc-8.6.3 + - ghc-8.6.4 + - ghc-8.6.5 + - ghc-8.8.1 + - ghc-8.8.2 + - ghc-8.8.3 + - ghc-8.8.4 + - ghc-8.10.1 + - ghc-8.10.2 + - ghc-8.10.3 + - ghc-8.10.4 + - ghc-8.10.5 + - ghc-8.10.6 + - ghc-8.10.7 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 7_8_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.8.1 + - 7_8_1-check: | + cd example.org + cabal check + - 7_8_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_8_1-build: | + cd example.org + cabal build all + - 7_8_1-test: | + cd example.org + cabal test all --enable-tests + - 7_8_1-haddock: | + cd example.org + cabal haddock all + - 7_8_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.8.2 + - 7_8_2-check: | + cd example.org + cabal check + - 7_8_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_8_2-build: | + cd example.org + cabal build all + - 7_8_2-test: | + cd example.org + cabal test all --enable-tests + - 7_8_2-haddock: | + cd example.org + cabal haddock all + - 7_8_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.8.3 + - 7_8_3-check: | + cd example.org + cabal check + - 7_8_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_8_3-build: | + cd example.org + cabal build all + - 7_8_3-test: | + cd example.org + cabal test all --enable-tests + - 7_8_3-haddock: | + cd example.org + cabal haddock all + - 7_8_4-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.8.4 + - 7_8_4-check: | + cd example.org + cabal check + - 7_8_4-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_8_4-build: | + cd example.org + cabal build all + - 7_8_4-test: | + cd example.org + cabal test all --enable-tests + - 7_8_4-haddock: | + cd example.org + cabal haddock all + - 7_10_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.10.1 + - 7_10_1-check: | + cd example.org + cabal check + - 7_10_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_10_1-build: | + cd example.org + cabal build all + - 7_10_1-test: | + cd example.org + cabal test all --enable-tests + - 7_10_1-haddock: | + cd example.org + cabal haddock all + - 7_10_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.10.2 + - 7_10_2-check: | + cd example.org + cabal check + - 7_10_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_10_2-build: | + cd example.org + cabal build all + - 7_10_2-test: | + cd example.org + cabal test all --enable-tests + - 7_10_2-haddock: | + cd example.org + cabal haddock all + - 7_10_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.10.3 + - 7_10_3-check: | + cd example.org + cabal check + - 7_10_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_10_3-build: | + cd example.org + cabal build all + - 7_10_3-test: | + cd example.org + cabal test all --enable-tests + - 7_10_3-haddock: | + cd example.org + cabal haddock all + - 8_0_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.0.1 + - 8_0_1-check: | + cd example.org + cabal check + - 8_0_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_0_1-build: | + cd example.org + cabal build all + - 8_0_1-test: | + cd example.org + cabal test all --enable-tests + - 8_0_1-haddock: | + cd example.org + cabal haddock all + - 8_0_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.0.2 + - 8_0_2-check: | + cd example.org + cabal check + - 8_0_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_0_2-build: | + cd example.org + cabal build all + - 8_0_2-test: | + cd example.org + cabal test all --enable-tests + - 8_0_2-haddock: | + cd example.org + cabal haddock all + - 8_2_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.2.1 + - 8_2_1-check: | + cd example.org + cabal check + - 8_2_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_2_1-build: | + cd example.org + cabal build all + - 8_2_1-test: | + cd example.org + cabal test all --enable-tests + - 8_2_1-haddock: | + cd example.org + cabal haddock all + - 8_2_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.2.2 + - 8_2_2-check: | + cd example.org + cabal check + - 8_2_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_2_2-build: | + cd example.org + cabal build all + - 8_2_2-test: | + cd example.org + cabal test all --enable-tests + - 8_2_2-haddock: | + cd example.org + cabal haddock all + - 8_4_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.4.1 + - 8_4_1-check: | + cd example.org + cabal check + - 8_4_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_4_1-build: | + cd example.org + cabal build all + - 8_4_1-test: | + cd example.org + cabal test all --enable-tests + - 8_4_1-haddock: | + cd example.org + cabal haddock all + - 8_4_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.4.2 + - 8_4_2-check: | + cd example.org + cabal check + - 8_4_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_4_2-build: | + cd example.org + cabal build all + - 8_4_2-test: | + cd example.org + cabal test all --enable-tests + - 8_4_2-haddock: | + cd example.org + cabal haddock all + - 8_4_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.4.3 + - 8_4_3-check: | + cd example.org + cabal check + - 8_4_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_4_3-build: | + cd example.org + cabal build all + - 8_4_3-test: | + cd example.org + cabal test all --enable-tests + - 8_4_3-haddock: | + cd example.org + cabal haddock all + - 8_4_4-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.4.4 + - 8_4_4-check: | + cd example.org + cabal check + - 8_4_4-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_4_4-build: | + cd example.org + cabal build all + - 8_4_4-test: | + cd example.org + cabal test all --enable-tests + - 8_4_4-haddock: | + cd example.org + cabal haddock all + - 8_6_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.6.1 + - 8_6_1-check: | + cd example.org + cabal check + - 8_6_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_6_1-build: | + cd example.org + cabal build all + - 8_6_1-test: | + cd example.org + cabal test all --enable-tests + - 8_6_1-haddock: | + cd example.org + cabal haddock all + - 8_6_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.6.2 + - 8_6_2-check: | + cd example.org + cabal check + - 8_6_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_6_2-build: | + cd example.org + cabal build all + - 8_6_2-test: | + cd example.org + cabal test all --enable-tests + - 8_6_2-haddock: | + cd example.org + cabal haddock all + - 8_6_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.6.3 + - 8_6_3-check: | + cd example.org + cabal check + - 8_6_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_6_3-build: | + cd example.org + cabal build all + - 8_6_3-test: | + cd example.org + cabal test all --enable-tests + - 8_6_3-haddock: | + cd example.org + cabal haddock all + - 8_6_4-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.6.4 + - 8_6_4-check: | + cd example.org + cabal check + - 8_6_4-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_6_4-build: | + cd example.org + cabal build all + - 8_6_4-test: | + cd example.org + cabal test all --enable-tests + - 8_6_4-haddock: | + cd example.org + cabal haddock all + - 8_6_5-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.6.5 + - 8_6_5-check: | + cd example.org + cabal check + - 8_6_5-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_6_5-build: | + cd example.org + cabal build all + - 8_6_5-test: | + cd example.org + cabal test all --enable-tests + - 8_6_5-haddock: | + cd example.org + cabal haddock all + - 8_8_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.8.1 + - 8_8_1-check: | + cd example.org + cabal check + - 8_8_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_8_1-build: | + cd example.org + cabal build all + - 8_8_1-test: | + cd example.org + cabal test all --enable-tests + - 8_8_1-haddock: | + cd example.org + cabal haddock all + - 8_8_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.8.2 + - 8_8_2-check: | + cd example.org + cabal check + - 8_8_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_8_2-build: | + cd example.org + cabal build all + - 8_8_2-test: | + cd example.org + cabal test all --enable-tests + - 8_8_2-haddock: | + cd example.org + cabal haddock all + - 8_8_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.8.3 + - 8_8_3-check: | + cd example.org + cabal check + - 8_8_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_8_3-build: | + cd example.org + cabal build all + - 8_8_3-test: | + cd example.org + cabal test all --enable-tests + - 8_8_3-haddock: | + cd example.org + cabal haddock all + - 8_8_4-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.8.4 + - 8_8_4-check: | + cd example.org + cabal check + - 8_8_4-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_8_4-build: | + cd example.org + cabal build all + - 8_8_4-test: | + cd example.org + cabal test all --enable-tests + - 8_8_4-haddock: | + cd example.org + cabal haddock all + - 8_10_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.1 + - 8_10_1-check: | + cd example.org + cabal check + - 8_10_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_1-build: | + cd example.org + cabal build all + - 8_10_1-test: | + cd example.org + cabal test all --enable-tests + - 8_10_1-haddock: | + cd example.org + cabal haddock all + - 8_10_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.2 + - 8_10_2-check: | + cd example.org + cabal check + - 8_10_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_2-build: | + cd example.org + cabal build all + - 8_10_2-test: | + cd example.org + cabal test all --enable-tests + - 8_10_2-haddock: | + cd example.org + cabal haddock all + - 8_10_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.3 + - 8_10_3-check: | + cd example.org + cabal check + - 8_10_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_3-build: | + cd example.org + cabal build all + - 8_10_3-test: | + cd example.org + cabal test all --enable-tests + - 8_10_3-haddock: | + cd example.org + cabal haddock all + - 8_10_4-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.4 + - 8_10_4-check: | + cd example.org + cabal check + - 8_10_4-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_4-build: | + cd example.org + cabal build all + - 8_10_4-test: | + cd example.org + cabal test all --enable-tests + - 8_10_4-haddock: | + cd example.org + cabal haddock all + - 8_10_5-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.5 + - 8_10_5-check: | + cd example.org + cabal check + - 8_10_5-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_5-build: | + cd example.org + cabal build all + - 8_10_5-test: | + cd example.org + cabal test all --enable-tests + - 8_10_5-haddock: | + cd example.org + cabal haddock all + - 8_10_6-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.6 + - 8_10_6-check: | + cd example.org + cabal check + - 8_10_6-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_6-build: | + cd example.org + cabal build all + - 8_10_6-test: | + cd example.org + cabal test all --enable-tests + - 8_10_6-haddock: | + cd example.org + cabal haddock all + - 8_10_7-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.7 + - 8_10_7-check: | + cd example.org + cabal check + - 8_10_7-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_7-build: | + cd example.org + cabal build all + - 8_10_7-test: | + cd example.org + cabal test all --enable-tests + - 8_10_7-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com diff --git a/fixtures/irc-channels.sourcehut-parallel b/fixtures/irc-channels.sourcehut-parallel new file mode 100644 index 00000000..2c8e4ac3 --- /dev/null +++ b/fixtures/irc-channels.sourcehut-parallel @@ -0,0 +1,1552 @@ +# SUCCESS +# *INFO* Generating Sourcehut config for testing for GHC versions: 7.8.1 7.8.2 7.8.3 7.8.4 7.10.1 7.10.2 7.10.3 8.0.1 8.0.2 8.2.1 8.2.2 8.4.1 8.4.2 8.4.3 8.4.4 8.6.1 8.6.2 8.6.3 8.6.4 8.6.5 8.8.1 8.8.2 8.8.3 8.8.4 8.10.1 8.10.2 8.10.3 8.10.4 8.10.5 8.10.6 8.10.7 +# manifest name: 7.10.1 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--irc-channels=irc.libera.chat#mychannel' 'sourcehut' 'irc-channels.project' +# +# 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 +# +# REGENDATA ["--irc-channels=irc.libera.chat#mychannel","sourcehut","irc-channels.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-7.10.1 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 7_10_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.10.1 + - 7_10_1-check: | + cd example.org + cabal check + - 7_10_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_10_1-build: | + cd example.org + cabal build all + - 7_10_1-test: | + cd example.org + cabal test all --enable-tests + - 7_10_1-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 7.10.2 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--irc-channels=irc.libera.chat#mychannel' 'sourcehut' 'irc-channels.project' +# +# 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 +# +# REGENDATA ["--irc-channels=irc.libera.chat#mychannel","sourcehut","irc-channels.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-7.10.2 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 7_10_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.10.2 + - 7_10_2-check: | + cd example.org + cabal check + - 7_10_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_10_2-build: | + cd example.org + cabal build all + - 7_10_2-test: | + cd example.org + cabal test all --enable-tests + - 7_10_2-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 7.10.3 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--irc-channels=irc.libera.chat#mychannel' 'sourcehut' 'irc-channels.project' +# +# 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 +# +# REGENDATA ["--irc-channels=irc.libera.chat#mychannel","sourcehut","irc-channels.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-7.10.3 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 7_10_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.10.3 + - 7_10_3-check: | + cd example.org + cabal check + - 7_10_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_10_3-build: | + cd example.org + cabal build all + - 7_10_3-test: | + cd example.org + cabal test all --enable-tests + - 7_10_3-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 7.8.1 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--irc-channels=irc.libera.chat#mychannel' 'sourcehut' 'irc-channels.project' +# +# 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 +# +# REGENDATA ["--irc-channels=irc.libera.chat#mychannel","sourcehut","irc-channels.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-7.8.1 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 7_8_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.8.1 + - 7_8_1-check: | + cd example.org + cabal check + - 7_8_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_8_1-build: | + cd example.org + cabal build all + - 7_8_1-test: | + cd example.org + cabal test all --enable-tests + - 7_8_1-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 7.8.2 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--irc-channels=irc.libera.chat#mychannel' 'sourcehut' 'irc-channels.project' +# +# 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 +# +# REGENDATA ["--irc-channels=irc.libera.chat#mychannel","sourcehut","irc-channels.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-7.8.2 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 7_8_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.8.2 + - 7_8_2-check: | + cd example.org + cabal check + - 7_8_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_8_2-build: | + cd example.org + cabal build all + - 7_8_2-test: | + cd example.org + cabal test all --enable-tests + - 7_8_2-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 7.8.3 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--irc-channels=irc.libera.chat#mychannel' 'sourcehut' 'irc-channels.project' +# +# 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 +# +# REGENDATA ["--irc-channels=irc.libera.chat#mychannel","sourcehut","irc-channels.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-7.8.3 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 7_8_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.8.3 + - 7_8_3-check: | + cd example.org + cabal check + - 7_8_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_8_3-build: | + cd example.org + cabal build all + - 7_8_3-test: | + cd example.org + cabal test all --enable-tests + - 7_8_3-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 7.8.4 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--irc-channels=irc.libera.chat#mychannel' 'sourcehut' 'irc-channels.project' +# +# 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 +# +# REGENDATA ["--irc-channels=irc.libera.chat#mychannel","sourcehut","irc-channels.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-7.8.4 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 7_8_4-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.8.4 + - 7_8_4-check: | + cd example.org + cabal check + - 7_8_4-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_8_4-build: | + cd example.org + cabal build all + - 7_8_4-test: | + cd example.org + cabal test all --enable-tests + - 7_8_4-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.0.1 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--irc-channels=irc.libera.chat#mychannel' 'sourcehut' 'irc-channels.project' +# +# 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 +# +# REGENDATA ["--irc-channels=irc.libera.chat#mychannel","sourcehut","irc-channels.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.0.1 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_0_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.0.1 + - 8_0_1-check: | + cd example.org + cabal check + - 8_0_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_0_1-build: | + cd example.org + cabal build all + - 8_0_1-test: | + cd example.org + cabal test all --enable-tests + - 8_0_1-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.0.2 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--irc-channels=irc.libera.chat#mychannel' 'sourcehut' 'irc-channels.project' +# +# 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 +# +# REGENDATA ["--irc-channels=irc.libera.chat#mychannel","sourcehut","irc-channels.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.0.2 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_0_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.0.2 + - 8_0_2-check: | + cd example.org + cabal check + - 8_0_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_0_2-build: | + cd example.org + cabal build all + - 8_0_2-test: | + cd example.org + cabal test all --enable-tests + - 8_0_2-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.10.1 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--irc-channels=irc.libera.chat#mychannel' 'sourcehut' 'irc-channels.project' +# +# 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 +# +# REGENDATA ["--irc-channels=irc.libera.chat#mychannel","sourcehut","irc-channels.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.10.1 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_10_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.1 + - 8_10_1-check: | + cd example.org + cabal check + - 8_10_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_1-build: | + cd example.org + cabal build all + - 8_10_1-test: | + cd example.org + cabal test all --enable-tests + - 8_10_1-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.10.2 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--irc-channels=irc.libera.chat#mychannel' 'sourcehut' 'irc-channels.project' +# +# 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 +# +# REGENDATA ["--irc-channels=irc.libera.chat#mychannel","sourcehut","irc-channels.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.10.2 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_10_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.2 + - 8_10_2-check: | + cd example.org + cabal check + - 8_10_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_2-build: | + cd example.org + cabal build all + - 8_10_2-test: | + cd example.org + cabal test all --enable-tests + - 8_10_2-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.10.3 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--irc-channels=irc.libera.chat#mychannel' 'sourcehut' 'irc-channels.project' +# +# 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 +# +# REGENDATA ["--irc-channels=irc.libera.chat#mychannel","sourcehut","irc-channels.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.10.3 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_10_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.3 + - 8_10_3-check: | + cd example.org + cabal check + - 8_10_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_3-build: | + cd example.org + cabal build all + - 8_10_3-test: | + cd example.org + cabal test all --enable-tests + - 8_10_3-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.10.4 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--irc-channels=irc.libera.chat#mychannel' 'sourcehut' 'irc-channels.project' +# +# 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 +# +# REGENDATA ["--irc-channels=irc.libera.chat#mychannel","sourcehut","irc-channels.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.10.4 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_10_4-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.4 + - 8_10_4-check: | + cd example.org + cabal check + - 8_10_4-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_4-build: | + cd example.org + cabal build all + - 8_10_4-test: | + cd example.org + cabal test all --enable-tests + - 8_10_4-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.10.5 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--irc-channels=irc.libera.chat#mychannel' 'sourcehut' 'irc-channels.project' +# +# 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 +# +# REGENDATA ["--irc-channels=irc.libera.chat#mychannel","sourcehut","irc-channels.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.10.5 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_10_5-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.5 + - 8_10_5-check: | + cd example.org + cabal check + - 8_10_5-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_5-build: | + cd example.org + cabal build all + - 8_10_5-test: | + cd example.org + cabal test all --enable-tests + - 8_10_5-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.10.6 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--irc-channels=irc.libera.chat#mychannel' 'sourcehut' 'irc-channels.project' +# +# 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 +# +# REGENDATA ["--irc-channels=irc.libera.chat#mychannel","sourcehut","irc-channels.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.10.6 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_10_6-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.6 + - 8_10_6-check: | + cd example.org + cabal check + - 8_10_6-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_6-build: | + cd example.org + cabal build all + - 8_10_6-test: | + cd example.org + cabal test all --enable-tests + - 8_10_6-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.10.7 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--irc-channels=irc.libera.chat#mychannel' 'sourcehut' 'irc-channels.project' +# +# 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 +# +# REGENDATA ["--irc-channels=irc.libera.chat#mychannel","sourcehut","irc-channels.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.10.7 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_10_7-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.7 + - 8_10_7-check: | + cd example.org + cabal check + - 8_10_7-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_7-build: | + cd example.org + cabal build all + - 8_10_7-test: | + cd example.org + cabal test all --enable-tests + - 8_10_7-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.2.1 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--irc-channels=irc.libera.chat#mychannel' 'sourcehut' 'irc-channels.project' +# +# 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 +# +# REGENDATA ["--irc-channels=irc.libera.chat#mychannel","sourcehut","irc-channels.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.2.1 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_2_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.2.1 + - 8_2_1-check: | + cd example.org + cabal check + - 8_2_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_2_1-build: | + cd example.org + cabal build all + - 8_2_1-test: | + cd example.org + cabal test all --enable-tests + - 8_2_1-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.2.2 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--irc-channels=irc.libera.chat#mychannel' 'sourcehut' 'irc-channels.project' +# +# 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 +# +# REGENDATA ["--irc-channels=irc.libera.chat#mychannel","sourcehut","irc-channels.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.2.2 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_2_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.2.2 + - 8_2_2-check: | + cd example.org + cabal check + - 8_2_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_2_2-build: | + cd example.org + cabal build all + - 8_2_2-test: | + cd example.org + cabal test all --enable-tests + - 8_2_2-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.4.1 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--irc-channels=irc.libera.chat#mychannel' 'sourcehut' 'irc-channels.project' +# +# 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 +# +# REGENDATA ["--irc-channels=irc.libera.chat#mychannel","sourcehut","irc-channels.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.4.1 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_4_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.4.1 + - 8_4_1-check: | + cd example.org + cabal check + - 8_4_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_4_1-build: | + cd example.org + cabal build all + - 8_4_1-test: | + cd example.org + cabal test all --enable-tests + - 8_4_1-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.4.2 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--irc-channels=irc.libera.chat#mychannel' 'sourcehut' 'irc-channels.project' +# +# 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 +# +# REGENDATA ["--irc-channels=irc.libera.chat#mychannel","sourcehut","irc-channels.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.4.2 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_4_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.4.2 + - 8_4_2-check: | + cd example.org + cabal check + - 8_4_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_4_2-build: | + cd example.org + cabal build all + - 8_4_2-test: | + cd example.org + cabal test all --enable-tests + - 8_4_2-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.4.3 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--irc-channels=irc.libera.chat#mychannel' 'sourcehut' 'irc-channels.project' +# +# 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 +# +# REGENDATA ["--irc-channels=irc.libera.chat#mychannel","sourcehut","irc-channels.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.4.3 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_4_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.4.3 + - 8_4_3-check: | + cd example.org + cabal check + - 8_4_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_4_3-build: | + cd example.org + cabal build all + - 8_4_3-test: | + cd example.org + cabal test all --enable-tests + - 8_4_3-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.4.4 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--irc-channels=irc.libera.chat#mychannel' 'sourcehut' 'irc-channels.project' +# +# 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 +# +# REGENDATA ["--irc-channels=irc.libera.chat#mychannel","sourcehut","irc-channels.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.4.4 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_4_4-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.4.4 + - 8_4_4-check: | + cd example.org + cabal check + - 8_4_4-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_4_4-build: | + cd example.org + cabal build all + - 8_4_4-test: | + cd example.org + cabal test all --enable-tests + - 8_4_4-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.6.1 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--irc-channels=irc.libera.chat#mychannel' 'sourcehut' 'irc-channels.project' +# +# 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 +# +# REGENDATA ["--irc-channels=irc.libera.chat#mychannel","sourcehut","irc-channels.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.6.1 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_6_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.6.1 + - 8_6_1-check: | + cd example.org + cabal check + - 8_6_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_6_1-build: | + cd example.org + cabal build all + - 8_6_1-test: | + cd example.org + cabal test all --enable-tests + - 8_6_1-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.6.2 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--irc-channels=irc.libera.chat#mychannel' 'sourcehut' 'irc-channels.project' +# +# 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 +# +# REGENDATA ["--irc-channels=irc.libera.chat#mychannel","sourcehut","irc-channels.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.6.2 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_6_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.6.2 + - 8_6_2-check: | + cd example.org + cabal check + - 8_6_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_6_2-build: | + cd example.org + cabal build all + - 8_6_2-test: | + cd example.org + cabal test all --enable-tests + - 8_6_2-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.6.3 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--irc-channels=irc.libera.chat#mychannel' 'sourcehut' 'irc-channels.project' +# +# 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 +# +# REGENDATA ["--irc-channels=irc.libera.chat#mychannel","sourcehut","irc-channels.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.6.3 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_6_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.6.3 + - 8_6_3-check: | + cd example.org + cabal check + - 8_6_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_6_3-build: | + cd example.org + cabal build all + - 8_6_3-test: | + cd example.org + cabal test all --enable-tests + - 8_6_3-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.6.4 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--irc-channels=irc.libera.chat#mychannel' 'sourcehut' 'irc-channels.project' +# +# 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 +# +# REGENDATA ["--irc-channels=irc.libera.chat#mychannel","sourcehut","irc-channels.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.6.4 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_6_4-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.6.4 + - 8_6_4-check: | + cd example.org + cabal check + - 8_6_4-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_6_4-build: | + cd example.org + cabal build all + - 8_6_4-test: | + cd example.org + cabal test all --enable-tests + - 8_6_4-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.6.5 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--irc-channels=irc.libera.chat#mychannel' 'sourcehut' 'irc-channels.project' +# +# 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 +# +# REGENDATA ["--irc-channels=irc.libera.chat#mychannel","sourcehut","irc-channels.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.6.5 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_6_5-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.6.5 + - 8_6_5-check: | + cd example.org + cabal check + - 8_6_5-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_6_5-build: | + cd example.org + cabal build all + - 8_6_5-test: | + cd example.org + cabal test all --enable-tests + - 8_6_5-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.8.1 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--irc-channels=irc.libera.chat#mychannel' 'sourcehut' 'irc-channels.project' +# +# 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 +# +# REGENDATA ["--irc-channels=irc.libera.chat#mychannel","sourcehut","irc-channels.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.8.1 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_8_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.8.1 + - 8_8_1-check: | + cd example.org + cabal check + - 8_8_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_8_1-build: | + cd example.org + cabal build all + - 8_8_1-test: | + cd example.org + cabal test all --enable-tests + - 8_8_1-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.8.2 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--irc-channels=irc.libera.chat#mychannel' 'sourcehut' 'irc-channels.project' +# +# 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 +# +# REGENDATA ["--irc-channels=irc.libera.chat#mychannel","sourcehut","irc-channels.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.8.2 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_8_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.8.2 + - 8_8_2-check: | + cd example.org + cabal check + - 8_8_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_8_2-build: | + cd example.org + cabal build all + - 8_8_2-test: | + cd example.org + cabal test all --enable-tests + - 8_8_2-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.8.3 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--irc-channels=irc.libera.chat#mychannel' 'sourcehut' 'irc-channels.project' +# +# 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 +# +# REGENDATA ["--irc-channels=irc.libera.chat#mychannel","sourcehut","irc-channels.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.8.3 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_8_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.8.3 + - 8_8_3-check: | + cd example.org + cabal check + - 8_8_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_8_3-build: | + cd example.org + cabal build all + - 8_8_3-test: | + cd example.org + cabal test all --enable-tests + - 8_8_3-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.8.4 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--irc-channels=irc.libera.chat#mychannel' 'sourcehut' 'irc-channels.project' +# +# 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 +# +# REGENDATA ["--irc-channels=irc.libera.chat#mychannel","sourcehut","irc-channels.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.8.4 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_8_4-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.8.4 + - 8_8_4-check: | + cd example.org + cabal check + - 8_8_4-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_8_4-build: | + cd example.org + cabal build all + - 8_8_4-test: | + cd example.org + cabal test all --enable-tests + - 8_8_4-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com diff --git a/fixtures/messy.sourcehut b/fixtures/messy.sourcehut new file mode 100644 index 00000000..b5414979 --- /dev/null +++ b/fixtures/messy.sourcehut @@ -0,0 +1,673 @@ +# SUCCESS +# *INFO* Generating Sourcehut config for testing for GHC versions: ghc-head 7.8.1 7.8.2 7.8.3 7.8.4 7.10.1 7.10.2 7.10.3 8.0.1 8.0.2 8.2.1 8.2.2 8.4.1 8.4.2 8.4.3 8.4.4 8.6.1 8.6.2 8.6.3 8.6.4 8.6.5 8.8.1 8.8.2 8.8.3 8.8.4 8.10.1 8.10.2 8.10.3 8.10.4 8.10.5 8.10.6 8.10.7 +# manifest name: all +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--ghc-head' '--apt=fftw3-dev' '--installed=-all +deepseq' 'sourcehut' 'messy.project' +# +# 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 +# +# REGENDATA ["--ghc-head","--apt=fftw3-dev","--installed=-all +deepseq","sourcehut","messy.project"] +# +image: ubuntu/bionic +packages: + - fftw3-dev + - gcc + - cabal-install-3.4 + - ghc-head + - ghc-7.8.1 + - ghc-7.8.2 + - ghc-7.8.3 + - ghc-7.8.4 + - ghc-7.10.1 + - ghc-7.10.2 + - ghc-7.10.3 + - ghc-8.0.1 + - ghc-8.0.2 + - ghc-8.2.1 + - ghc-8.2.2 + - ghc-8.4.1 + - ghc-8.4.2 + - ghc-8.4.3 + - ghc-8.4.4 + - ghc-8.6.1 + - ghc-8.6.2 + - ghc-8.6.3 + - ghc-8.6.4 + - ghc-8.6.5 + - ghc-8.8.1 + - ghc-8.8.2 + - ghc-8.8.3 + - ghc-8.8.4 + - ghc-8.10.1 + - ghc-8.10.2 + - ghc-8.10.3 + - ghc-8.10.4 + - ghc-8.10.5 + - ghc-8.10.6 + - ghc-8.10.7 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - ghc-head-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-head + - ghc-head-check: | + cd example.org + cabal check + - ghc-head-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - ghc-head-build: | + cd example.org + cabal build all + - ghc-head-test: | + cd example.org + cabal test all --enable-tests + - ghc-head-haddock: | + cd example.org + cabal haddock all + - 7_8_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.8.1 + - 7_8_1-check: | + cd example.org + cabal check + - 7_8_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_8_1-build: | + cd example.org + cabal build all + - 7_8_1-test: | + cd example.org + cabal test all --enable-tests + - 7_8_1-haddock: | + cd example.org + cabal haddock all + - 7_8_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.8.2 + - 7_8_2-check: | + cd example.org + cabal check + - 7_8_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_8_2-build: | + cd example.org + cabal build all + - 7_8_2-test: | + cd example.org + cabal test all --enable-tests + - 7_8_2-haddock: | + cd example.org + cabal haddock all + - 7_8_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.8.3 + - 7_8_3-check: | + cd example.org + cabal check + - 7_8_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_8_3-build: | + cd example.org + cabal build all + - 7_8_3-test: | + cd example.org + cabal test all --enable-tests + - 7_8_3-haddock: | + cd example.org + cabal haddock all + - 7_8_4-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.8.4 + - 7_8_4-check: | + cd example.org + cabal check + - 7_8_4-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_8_4-build: | + cd example.org + cabal build all + - 7_8_4-test: | + cd example.org + cabal test all --enable-tests + - 7_8_4-haddock: | + cd example.org + cabal haddock all + - 7_10_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.10.1 + - 7_10_1-check: | + cd example.org + cabal check + - 7_10_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_10_1-build: | + cd example.org + cabal build all + - 7_10_1-test: | + cd example.org + cabal test all --enable-tests + - 7_10_1-haddock: | + cd example.org + cabal haddock all + - 7_10_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.10.2 + - 7_10_2-check: | + cd example.org + cabal check + - 7_10_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_10_2-build: | + cd example.org + cabal build all + - 7_10_2-test: | + cd example.org + cabal test all --enable-tests + - 7_10_2-haddock: | + cd example.org + cabal haddock all + - 7_10_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.10.3 + - 7_10_3-check: | + cd example.org + cabal check + - 7_10_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_10_3-build: | + cd example.org + cabal build all + - 7_10_3-test: | + cd example.org + cabal test all --enable-tests + - 7_10_3-haddock: | + cd example.org + cabal haddock all + - 8_0_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.0.1 + - 8_0_1-check: | + cd example.org + cabal check + - 8_0_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_0_1-build: | + cd example.org + cabal build all + - 8_0_1-test: | + cd example.org + cabal test all --enable-tests + - 8_0_1-haddock: | + cd example.org + cabal haddock all + - 8_0_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.0.2 + - 8_0_2-check: | + cd example.org + cabal check + - 8_0_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_0_2-build: | + cd example.org + cabal build all + - 8_0_2-test: | + cd example.org + cabal test all --enable-tests + - 8_0_2-haddock: | + cd example.org + cabal haddock all + - 8_2_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.2.1 + - 8_2_1-check: | + cd example.org + cabal check + - 8_2_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_2_1-build: | + cd example.org + cabal build all + - 8_2_1-test: | + cd example.org + cabal test all --enable-tests + - 8_2_1-haddock: | + cd example.org + cabal haddock all + - 8_2_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.2.2 + - 8_2_2-check: | + cd example.org + cabal check + - 8_2_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_2_2-build: | + cd example.org + cabal build all + - 8_2_2-test: | + cd example.org + cabal test all --enable-tests + - 8_2_2-haddock: | + cd example.org + cabal haddock all + - 8_4_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.4.1 + - 8_4_1-check: | + cd example.org + cabal check + - 8_4_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_4_1-build: | + cd example.org + cabal build all + - 8_4_1-test: | + cd example.org + cabal test all --enable-tests + - 8_4_1-haddock: | + cd example.org + cabal haddock all + - 8_4_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.4.2 + - 8_4_2-check: | + cd example.org + cabal check + - 8_4_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_4_2-build: | + cd example.org + cabal build all + - 8_4_2-test: | + cd example.org + cabal test all --enable-tests + - 8_4_2-haddock: | + cd example.org + cabal haddock all + - 8_4_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.4.3 + - 8_4_3-check: | + cd example.org + cabal check + - 8_4_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_4_3-build: | + cd example.org + cabal build all + - 8_4_3-test: | + cd example.org + cabal test all --enable-tests + - 8_4_3-haddock: | + cd example.org + cabal haddock all + - 8_4_4-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.4.4 + - 8_4_4-check: | + cd example.org + cabal check + - 8_4_4-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_4_4-build: | + cd example.org + cabal build all + - 8_4_4-test: | + cd example.org + cabal test all --enable-tests + - 8_4_4-haddock: | + cd example.org + cabal haddock all + - 8_6_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.6.1 + - 8_6_1-check: | + cd example.org + cabal check + - 8_6_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_6_1-build: | + cd example.org + cabal build all + - 8_6_1-test: | + cd example.org + cabal test all --enable-tests + - 8_6_1-haddock: | + cd example.org + cabal haddock all + - 8_6_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.6.2 + - 8_6_2-check: | + cd example.org + cabal check + - 8_6_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_6_2-build: | + cd example.org + cabal build all + - 8_6_2-test: | + cd example.org + cabal test all --enable-tests + - 8_6_2-haddock: | + cd example.org + cabal haddock all + - 8_6_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.6.3 + - 8_6_3-check: | + cd example.org + cabal check + - 8_6_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_6_3-build: | + cd example.org + cabal build all + - 8_6_3-test: | + cd example.org + cabal test all --enable-tests + - 8_6_3-haddock: | + cd example.org + cabal haddock all + - 8_6_4-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.6.4 + - 8_6_4-check: | + cd example.org + cabal check + - 8_6_4-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_6_4-build: | + cd example.org + cabal build all + - 8_6_4-test: | + cd example.org + cabal test all --enable-tests + - 8_6_4-haddock: | + cd example.org + cabal haddock all + - 8_6_5-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.6.5 + - 8_6_5-check: | + cd example.org + cabal check + - 8_6_5-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_6_5-build: | + cd example.org + cabal build all + - 8_6_5-test: | + cd example.org + cabal test all --enable-tests + - 8_6_5-haddock: | + cd example.org + cabal haddock all + - 8_8_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.8.1 + - 8_8_1-check: | + cd example.org + cabal check + - 8_8_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_8_1-build: | + cd example.org + cabal build all + - 8_8_1-test: | + cd example.org + cabal test all --enable-tests + - 8_8_1-haddock: | + cd example.org + cabal haddock all + - 8_8_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.8.2 + - 8_8_2-check: | + cd example.org + cabal check + - 8_8_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_8_2-build: | + cd example.org + cabal build all + - 8_8_2-test: | + cd example.org + cabal test all --enable-tests + - 8_8_2-haddock: | + cd example.org + cabal haddock all + - 8_8_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.8.3 + - 8_8_3-check: | + cd example.org + cabal check + - 8_8_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_8_3-build: | + cd example.org + cabal build all + - 8_8_3-test: | + cd example.org + cabal test all --enable-tests + - 8_8_3-haddock: | + cd example.org + cabal haddock all + - 8_8_4-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.8.4 + - 8_8_4-check: | + cd example.org + cabal check + - 8_8_4-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_8_4-build: | + cd example.org + cabal build all + - 8_8_4-test: | + cd example.org + cabal test all --enable-tests + - 8_8_4-haddock: | + cd example.org + cabal haddock all + - 8_10_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.1 + - 8_10_1-check: | + cd example.org + cabal check + - 8_10_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_1-build: | + cd example.org + cabal build all + - 8_10_1-test: | + cd example.org + cabal test all --enable-tests + - 8_10_1-haddock: | + cd example.org + cabal haddock all + - 8_10_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.2 + - 8_10_2-check: | + cd example.org + cabal check + - 8_10_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_2-build: | + cd example.org + cabal build all + - 8_10_2-test: | + cd example.org + cabal test all --enable-tests + - 8_10_2-haddock: | + cd example.org + cabal haddock all + - 8_10_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.3 + - 8_10_3-check: | + cd example.org + cabal check + - 8_10_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_3-build: | + cd example.org + cabal build all + - 8_10_3-test: | + cd example.org + cabal test all --enable-tests + - 8_10_3-haddock: | + cd example.org + cabal haddock all + - 8_10_4-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.4 + - 8_10_4-check: | + cd example.org + cabal check + - 8_10_4-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_4-build: | + cd example.org + cabal build all + - 8_10_4-test: | + cd example.org + cabal test all --enable-tests + - 8_10_4-haddock: | + cd example.org + cabal haddock all + - 8_10_5-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.5 + - 8_10_5-check: | + cd example.org + cabal check + - 8_10_5-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_5-build: | + cd example.org + cabal build all + - 8_10_5-test: | + cd example.org + cabal test all --enable-tests + - 8_10_5-haddock: | + cd example.org + cabal haddock all + - 8_10_6-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.6 + - 8_10_6-check: | + cd example.org + cabal check + - 8_10_6-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_6-build: | + cd example.org + cabal build all + - 8_10_6-test: | + cd example.org + cabal test all --enable-tests + - 8_10_6-haddock: | + cd example.org + cabal haddock all + - 8_10_7-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.7 + - 8_10_7-check: | + cd example.org + cabal check + - 8_10_7-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_7-build: | + cd example.org + cabal build all + - 8_10_7-test: | + cd example.org + cabal test all --enable-tests + - 8_10_7-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com diff --git a/fixtures/messy.sourcehut-parallel b/fixtures/messy.sourcehut-parallel new file mode 100644 index 00000000..bfdfe8ac --- /dev/null +++ b/fixtures/messy.sourcehut-parallel @@ -0,0 +1,1634 @@ +# SUCCESS +# *INFO* Generating Sourcehut config for testing for GHC versions: ghc-head 7.8.1 7.8.2 7.8.3 7.8.4 7.10.1 7.10.2 7.10.3 8.0.1 8.0.2 8.2.1 8.2.2 8.4.1 8.4.2 8.4.3 8.4.4 8.6.1 8.6.2 8.6.3 8.6.4 8.6.5 8.8.1 8.8.2 8.8.3 8.8.4 8.10.1 8.10.2 8.10.3 8.10.4 8.10.5 8.10.6 8.10.7 +# manifest name: 7.10.1 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--ghc-head' '--apt=fftw3-dev' '--installed=-all +deepseq' 'sourcehut' 'messy.project' +# +# 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 +# +# REGENDATA ["--ghc-head","--apt=fftw3-dev","--installed=-all +deepseq","sourcehut","messy.project"] +# +image: ubuntu/bionic +packages: + - fftw3-dev + - gcc + - cabal-install-3.4 + - ghc-7.10.1 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 7_10_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.10.1 + - 7_10_1-check: | + cd example.org + cabal check + - 7_10_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_10_1-build: | + cd example.org + cabal build all + - 7_10_1-test: | + cd example.org + cabal test all --enable-tests + - 7_10_1-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 7.10.2 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--ghc-head' '--apt=fftw3-dev' '--installed=-all +deepseq' 'sourcehut' 'messy.project' +# +# 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 +# +# REGENDATA ["--ghc-head","--apt=fftw3-dev","--installed=-all +deepseq","sourcehut","messy.project"] +# +image: ubuntu/bionic +packages: + - fftw3-dev + - gcc + - cabal-install-3.4 + - ghc-7.10.2 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 7_10_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.10.2 + - 7_10_2-check: | + cd example.org + cabal check + - 7_10_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_10_2-build: | + cd example.org + cabal build all + - 7_10_2-test: | + cd example.org + cabal test all --enable-tests + - 7_10_2-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 7.10.3 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--ghc-head' '--apt=fftw3-dev' '--installed=-all +deepseq' 'sourcehut' 'messy.project' +# +# 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 +# +# REGENDATA ["--ghc-head","--apt=fftw3-dev","--installed=-all +deepseq","sourcehut","messy.project"] +# +image: ubuntu/bionic +packages: + - fftw3-dev + - gcc + - cabal-install-3.4 + - ghc-7.10.3 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 7_10_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.10.3 + - 7_10_3-check: | + cd example.org + cabal check + - 7_10_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_10_3-build: | + cd example.org + cabal build all + - 7_10_3-test: | + cd example.org + cabal test all --enable-tests + - 7_10_3-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 7.8.1 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--ghc-head' '--apt=fftw3-dev' '--installed=-all +deepseq' 'sourcehut' 'messy.project' +# +# 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 +# +# REGENDATA ["--ghc-head","--apt=fftw3-dev","--installed=-all +deepseq","sourcehut","messy.project"] +# +image: ubuntu/bionic +packages: + - fftw3-dev + - gcc + - cabal-install-3.4 + - ghc-7.8.1 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 7_8_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.8.1 + - 7_8_1-check: | + cd example.org + cabal check + - 7_8_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_8_1-build: | + cd example.org + cabal build all + - 7_8_1-test: | + cd example.org + cabal test all --enable-tests + - 7_8_1-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 7.8.2 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--ghc-head' '--apt=fftw3-dev' '--installed=-all +deepseq' 'sourcehut' 'messy.project' +# +# 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 +# +# REGENDATA ["--ghc-head","--apt=fftw3-dev","--installed=-all +deepseq","sourcehut","messy.project"] +# +image: ubuntu/bionic +packages: + - fftw3-dev + - gcc + - cabal-install-3.4 + - ghc-7.8.2 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 7_8_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.8.2 + - 7_8_2-check: | + cd example.org + cabal check + - 7_8_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_8_2-build: | + cd example.org + cabal build all + - 7_8_2-test: | + cd example.org + cabal test all --enable-tests + - 7_8_2-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 7.8.3 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--ghc-head' '--apt=fftw3-dev' '--installed=-all +deepseq' 'sourcehut' 'messy.project' +# +# 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 +# +# REGENDATA ["--ghc-head","--apt=fftw3-dev","--installed=-all +deepseq","sourcehut","messy.project"] +# +image: ubuntu/bionic +packages: + - fftw3-dev + - gcc + - cabal-install-3.4 + - ghc-7.8.3 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 7_8_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.8.3 + - 7_8_3-check: | + cd example.org + cabal check + - 7_8_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_8_3-build: | + cd example.org + cabal build all + - 7_8_3-test: | + cd example.org + cabal test all --enable-tests + - 7_8_3-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 7.8.4 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--ghc-head' '--apt=fftw3-dev' '--installed=-all +deepseq' 'sourcehut' 'messy.project' +# +# 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 +# +# REGENDATA ["--ghc-head","--apt=fftw3-dev","--installed=-all +deepseq","sourcehut","messy.project"] +# +image: ubuntu/bionic +packages: + - fftw3-dev + - gcc + - cabal-install-3.4 + - ghc-7.8.4 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 7_8_4-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.8.4 + - 7_8_4-check: | + cd example.org + cabal check + - 7_8_4-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_8_4-build: | + cd example.org + cabal build all + - 7_8_4-test: | + cd example.org + cabal test all --enable-tests + - 7_8_4-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.0.1 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--ghc-head' '--apt=fftw3-dev' '--installed=-all +deepseq' 'sourcehut' 'messy.project' +# +# 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 +# +# REGENDATA ["--ghc-head","--apt=fftw3-dev","--installed=-all +deepseq","sourcehut","messy.project"] +# +image: ubuntu/bionic +packages: + - fftw3-dev + - gcc + - cabal-install-3.4 + - ghc-8.0.1 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_0_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.0.1 + - 8_0_1-check: | + cd example.org + cabal check + - 8_0_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_0_1-build: | + cd example.org + cabal build all + - 8_0_1-test: | + cd example.org + cabal test all --enable-tests + - 8_0_1-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.0.2 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--ghc-head' '--apt=fftw3-dev' '--installed=-all +deepseq' 'sourcehut' 'messy.project' +# +# 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 +# +# REGENDATA ["--ghc-head","--apt=fftw3-dev","--installed=-all +deepseq","sourcehut","messy.project"] +# +image: ubuntu/bionic +packages: + - fftw3-dev + - gcc + - cabal-install-3.4 + - ghc-8.0.2 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_0_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.0.2 + - 8_0_2-check: | + cd example.org + cabal check + - 8_0_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_0_2-build: | + cd example.org + cabal build all + - 8_0_2-test: | + cd example.org + cabal test all --enable-tests + - 8_0_2-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.10.1 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--ghc-head' '--apt=fftw3-dev' '--installed=-all +deepseq' 'sourcehut' 'messy.project' +# +# 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 +# +# REGENDATA ["--ghc-head","--apt=fftw3-dev","--installed=-all +deepseq","sourcehut","messy.project"] +# +image: ubuntu/bionic +packages: + - fftw3-dev + - gcc + - cabal-install-3.4 + - ghc-8.10.1 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_10_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.1 + - 8_10_1-check: | + cd example.org + cabal check + - 8_10_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_1-build: | + cd example.org + cabal build all + - 8_10_1-test: | + cd example.org + cabal test all --enable-tests + - 8_10_1-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.10.2 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--ghc-head' '--apt=fftw3-dev' '--installed=-all +deepseq' 'sourcehut' 'messy.project' +# +# 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 +# +# REGENDATA ["--ghc-head","--apt=fftw3-dev","--installed=-all +deepseq","sourcehut","messy.project"] +# +image: ubuntu/bionic +packages: + - fftw3-dev + - gcc + - cabal-install-3.4 + - ghc-8.10.2 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_10_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.2 + - 8_10_2-check: | + cd example.org + cabal check + - 8_10_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_2-build: | + cd example.org + cabal build all + - 8_10_2-test: | + cd example.org + cabal test all --enable-tests + - 8_10_2-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.10.3 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--ghc-head' '--apt=fftw3-dev' '--installed=-all +deepseq' 'sourcehut' 'messy.project' +# +# 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 +# +# REGENDATA ["--ghc-head","--apt=fftw3-dev","--installed=-all +deepseq","sourcehut","messy.project"] +# +image: ubuntu/bionic +packages: + - fftw3-dev + - gcc + - cabal-install-3.4 + - ghc-8.10.3 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_10_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.3 + - 8_10_3-check: | + cd example.org + cabal check + - 8_10_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_3-build: | + cd example.org + cabal build all + - 8_10_3-test: | + cd example.org + cabal test all --enable-tests + - 8_10_3-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.10.4 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--ghc-head' '--apt=fftw3-dev' '--installed=-all +deepseq' 'sourcehut' 'messy.project' +# +# 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 +# +# REGENDATA ["--ghc-head","--apt=fftw3-dev","--installed=-all +deepseq","sourcehut","messy.project"] +# +image: ubuntu/bionic +packages: + - fftw3-dev + - gcc + - cabal-install-3.4 + - ghc-8.10.4 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_10_4-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.4 + - 8_10_4-check: | + cd example.org + cabal check + - 8_10_4-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_4-build: | + cd example.org + cabal build all + - 8_10_4-test: | + cd example.org + cabal test all --enable-tests + - 8_10_4-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.10.5 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--ghc-head' '--apt=fftw3-dev' '--installed=-all +deepseq' 'sourcehut' 'messy.project' +# +# 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 +# +# REGENDATA ["--ghc-head","--apt=fftw3-dev","--installed=-all +deepseq","sourcehut","messy.project"] +# +image: ubuntu/bionic +packages: + - fftw3-dev + - gcc + - cabal-install-3.4 + - ghc-8.10.5 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_10_5-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.5 + - 8_10_5-check: | + cd example.org + cabal check + - 8_10_5-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_5-build: | + cd example.org + cabal build all + - 8_10_5-test: | + cd example.org + cabal test all --enable-tests + - 8_10_5-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.10.6 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--ghc-head' '--apt=fftw3-dev' '--installed=-all +deepseq' 'sourcehut' 'messy.project' +# +# 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 +# +# REGENDATA ["--ghc-head","--apt=fftw3-dev","--installed=-all +deepseq","sourcehut","messy.project"] +# +image: ubuntu/bionic +packages: + - fftw3-dev + - gcc + - cabal-install-3.4 + - ghc-8.10.6 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_10_6-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.6 + - 8_10_6-check: | + cd example.org + cabal check + - 8_10_6-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_6-build: | + cd example.org + cabal build all + - 8_10_6-test: | + cd example.org + cabal test all --enable-tests + - 8_10_6-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.10.7 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--ghc-head' '--apt=fftw3-dev' '--installed=-all +deepseq' 'sourcehut' 'messy.project' +# +# 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 +# +# REGENDATA ["--ghc-head","--apt=fftw3-dev","--installed=-all +deepseq","sourcehut","messy.project"] +# +image: ubuntu/bionic +packages: + - fftw3-dev + - gcc + - cabal-install-3.4 + - ghc-8.10.7 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_10_7-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.7 + - 8_10_7-check: | + cd example.org + cabal check + - 8_10_7-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_7-build: | + cd example.org + cabal build all + - 8_10_7-test: | + cd example.org + cabal test all --enable-tests + - 8_10_7-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.2.1 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--ghc-head' '--apt=fftw3-dev' '--installed=-all +deepseq' 'sourcehut' 'messy.project' +# +# 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 +# +# REGENDATA ["--ghc-head","--apt=fftw3-dev","--installed=-all +deepseq","sourcehut","messy.project"] +# +image: ubuntu/bionic +packages: + - fftw3-dev + - gcc + - cabal-install-3.4 + - ghc-8.2.1 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_2_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.2.1 + - 8_2_1-check: | + cd example.org + cabal check + - 8_2_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_2_1-build: | + cd example.org + cabal build all + - 8_2_1-test: | + cd example.org + cabal test all --enable-tests + - 8_2_1-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.2.2 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--ghc-head' '--apt=fftw3-dev' '--installed=-all +deepseq' 'sourcehut' 'messy.project' +# +# 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 +# +# REGENDATA ["--ghc-head","--apt=fftw3-dev","--installed=-all +deepseq","sourcehut","messy.project"] +# +image: ubuntu/bionic +packages: + - fftw3-dev + - gcc + - cabal-install-3.4 + - ghc-8.2.2 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_2_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.2.2 + - 8_2_2-check: | + cd example.org + cabal check + - 8_2_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_2_2-build: | + cd example.org + cabal build all + - 8_2_2-test: | + cd example.org + cabal test all --enable-tests + - 8_2_2-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.4.1 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--ghc-head' '--apt=fftw3-dev' '--installed=-all +deepseq' 'sourcehut' 'messy.project' +# +# 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 +# +# REGENDATA ["--ghc-head","--apt=fftw3-dev","--installed=-all +deepseq","sourcehut","messy.project"] +# +image: ubuntu/bionic +packages: + - fftw3-dev + - gcc + - cabal-install-3.4 + - ghc-8.4.1 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_4_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.4.1 + - 8_4_1-check: | + cd example.org + cabal check + - 8_4_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_4_1-build: | + cd example.org + cabal build all + - 8_4_1-test: | + cd example.org + cabal test all --enable-tests + - 8_4_1-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.4.2 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--ghc-head' '--apt=fftw3-dev' '--installed=-all +deepseq' 'sourcehut' 'messy.project' +# +# 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 +# +# REGENDATA ["--ghc-head","--apt=fftw3-dev","--installed=-all +deepseq","sourcehut","messy.project"] +# +image: ubuntu/bionic +packages: + - fftw3-dev + - gcc + - cabal-install-3.4 + - ghc-8.4.2 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_4_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.4.2 + - 8_4_2-check: | + cd example.org + cabal check + - 8_4_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_4_2-build: | + cd example.org + cabal build all + - 8_4_2-test: | + cd example.org + cabal test all --enable-tests + - 8_4_2-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.4.3 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--ghc-head' '--apt=fftw3-dev' '--installed=-all +deepseq' 'sourcehut' 'messy.project' +# +# 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 +# +# REGENDATA ["--ghc-head","--apt=fftw3-dev","--installed=-all +deepseq","sourcehut","messy.project"] +# +image: ubuntu/bionic +packages: + - fftw3-dev + - gcc + - cabal-install-3.4 + - ghc-8.4.3 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_4_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.4.3 + - 8_4_3-check: | + cd example.org + cabal check + - 8_4_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_4_3-build: | + cd example.org + cabal build all + - 8_4_3-test: | + cd example.org + cabal test all --enable-tests + - 8_4_3-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.4.4 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--ghc-head' '--apt=fftw3-dev' '--installed=-all +deepseq' 'sourcehut' 'messy.project' +# +# 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 +# +# REGENDATA ["--ghc-head","--apt=fftw3-dev","--installed=-all +deepseq","sourcehut","messy.project"] +# +image: ubuntu/bionic +packages: + - fftw3-dev + - gcc + - cabal-install-3.4 + - ghc-8.4.4 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_4_4-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.4.4 + - 8_4_4-check: | + cd example.org + cabal check + - 8_4_4-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_4_4-build: | + cd example.org + cabal build all + - 8_4_4-test: | + cd example.org + cabal test all --enable-tests + - 8_4_4-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.6.1 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--ghc-head' '--apt=fftw3-dev' '--installed=-all +deepseq' 'sourcehut' 'messy.project' +# +# 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 +# +# REGENDATA ["--ghc-head","--apt=fftw3-dev","--installed=-all +deepseq","sourcehut","messy.project"] +# +image: ubuntu/bionic +packages: + - fftw3-dev + - gcc + - cabal-install-3.4 + - ghc-8.6.1 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_6_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.6.1 + - 8_6_1-check: | + cd example.org + cabal check + - 8_6_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_6_1-build: | + cd example.org + cabal build all + - 8_6_1-test: | + cd example.org + cabal test all --enable-tests + - 8_6_1-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.6.2 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--ghc-head' '--apt=fftw3-dev' '--installed=-all +deepseq' 'sourcehut' 'messy.project' +# +# 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 +# +# REGENDATA ["--ghc-head","--apt=fftw3-dev","--installed=-all +deepseq","sourcehut","messy.project"] +# +image: ubuntu/bionic +packages: + - fftw3-dev + - gcc + - cabal-install-3.4 + - ghc-8.6.2 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_6_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.6.2 + - 8_6_2-check: | + cd example.org + cabal check + - 8_6_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_6_2-build: | + cd example.org + cabal build all + - 8_6_2-test: | + cd example.org + cabal test all --enable-tests + - 8_6_2-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.6.3 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--ghc-head' '--apt=fftw3-dev' '--installed=-all +deepseq' 'sourcehut' 'messy.project' +# +# 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 +# +# REGENDATA ["--ghc-head","--apt=fftw3-dev","--installed=-all +deepseq","sourcehut","messy.project"] +# +image: ubuntu/bionic +packages: + - fftw3-dev + - gcc + - cabal-install-3.4 + - ghc-8.6.3 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_6_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.6.3 + - 8_6_3-check: | + cd example.org + cabal check + - 8_6_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_6_3-build: | + cd example.org + cabal build all + - 8_6_3-test: | + cd example.org + cabal test all --enable-tests + - 8_6_3-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.6.4 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--ghc-head' '--apt=fftw3-dev' '--installed=-all +deepseq' 'sourcehut' 'messy.project' +# +# 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 +# +# REGENDATA ["--ghc-head","--apt=fftw3-dev","--installed=-all +deepseq","sourcehut","messy.project"] +# +image: ubuntu/bionic +packages: + - fftw3-dev + - gcc + - cabal-install-3.4 + - ghc-8.6.4 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_6_4-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.6.4 + - 8_6_4-check: | + cd example.org + cabal check + - 8_6_4-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_6_4-build: | + cd example.org + cabal build all + - 8_6_4-test: | + cd example.org + cabal test all --enable-tests + - 8_6_4-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.6.5 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--ghc-head' '--apt=fftw3-dev' '--installed=-all +deepseq' 'sourcehut' 'messy.project' +# +# 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 +# +# REGENDATA ["--ghc-head","--apt=fftw3-dev","--installed=-all +deepseq","sourcehut","messy.project"] +# +image: ubuntu/bionic +packages: + - fftw3-dev + - gcc + - cabal-install-3.4 + - ghc-8.6.5 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_6_5-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.6.5 + - 8_6_5-check: | + cd example.org + cabal check + - 8_6_5-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_6_5-build: | + cd example.org + cabal build all + - 8_6_5-test: | + cd example.org + cabal test all --enable-tests + - 8_6_5-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.8.1 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--ghc-head' '--apt=fftw3-dev' '--installed=-all +deepseq' 'sourcehut' 'messy.project' +# +# 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 +# +# REGENDATA ["--ghc-head","--apt=fftw3-dev","--installed=-all +deepseq","sourcehut","messy.project"] +# +image: ubuntu/bionic +packages: + - fftw3-dev + - gcc + - cabal-install-3.4 + - ghc-8.8.1 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_8_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.8.1 + - 8_8_1-check: | + cd example.org + cabal check + - 8_8_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_8_1-build: | + cd example.org + cabal build all + - 8_8_1-test: | + cd example.org + cabal test all --enable-tests + - 8_8_1-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.8.2 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--ghc-head' '--apt=fftw3-dev' '--installed=-all +deepseq' 'sourcehut' 'messy.project' +# +# 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 +# +# REGENDATA ["--ghc-head","--apt=fftw3-dev","--installed=-all +deepseq","sourcehut","messy.project"] +# +image: ubuntu/bionic +packages: + - fftw3-dev + - gcc + - cabal-install-3.4 + - ghc-8.8.2 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_8_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.8.2 + - 8_8_2-check: | + cd example.org + cabal check + - 8_8_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_8_2-build: | + cd example.org + cabal build all + - 8_8_2-test: | + cd example.org + cabal test all --enable-tests + - 8_8_2-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.8.3 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--ghc-head' '--apt=fftw3-dev' '--installed=-all +deepseq' 'sourcehut' 'messy.project' +# +# 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 +# +# REGENDATA ["--ghc-head","--apt=fftw3-dev","--installed=-all +deepseq","sourcehut","messy.project"] +# +image: ubuntu/bionic +packages: + - fftw3-dev + - gcc + - cabal-install-3.4 + - ghc-8.8.3 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_8_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.8.3 + - 8_8_3-check: | + cd example.org + cabal check + - 8_8_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_8_3-build: | + cd example.org + cabal build all + - 8_8_3-test: | + cd example.org + cabal test all --enable-tests + - 8_8_3-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.8.4 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--ghc-head' '--apt=fftw3-dev' '--installed=-all +deepseq' 'sourcehut' 'messy.project' +# +# 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 +# +# REGENDATA ["--ghc-head","--apt=fftw3-dev","--installed=-all +deepseq","sourcehut","messy.project"] +# +image: ubuntu/bionic +packages: + - fftw3-dev + - gcc + - cabal-install-3.4 + - ghc-8.8.4 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_8_4-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.8.4 + - 8_8_4-check: | + cd example.org + cabal check + - 8_8_4-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_8_4-build: | + cd example.org + cabal build all + - 8_8_4-test: | + cd example.org + cabal test all --enable-tests + - 8_8_4-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: ghc-head +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--ghc-head' '--apt=fftw3-dev' '--installed=-all +deepseq' 'sourcehut' 'messy.project' +# +# 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 +# +# REGENDATA ["--ghc-head","--apt=fftw3-dev","--installed=-all +deepseq","sourcehut","messy.project"] +# +image: ubuntu/bionic +packages: + - fftw3-dev + - gcc + - cabal-install-3.4 + - ghc-head +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - ghc-head-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-head + - ghc-head-check: | + cd example.org + cabal check + - ghc-head-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - ghc-head-build: | + cd example.org + cabal build all + - ghc-head-test: | + cd example.org + cabal test all --enable-tests + - ghc-head-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com diff --git a/fixtures/psql.sourcehut b/fixtures/psql.sourcehut new file mode 100644 index 00000000..630036c1 --- /dev/null +++ b/fixtures/psql.sourcehut @@ -0,0 +1,652 @@ +# SUCCESS +# *INFO* Generating Sourcehut config for testing for GHC versions: 7.8.1 7.8.2 7.8.3 7.8.4 7.10.1 7.10.2 7.10.3 8.0.1 8.0.2 8.2.1 8.2.2 8.4.1 8.4.2 8.4.3 8.4.4 8.6.1 8.6.2 8.6.3 8.6.4 8.6.5 8.8.1 8.8.2 8.8.3 8.8.4 8.10.1 8.10.2 8.10.3 8.10.4 8.10.5 8.10.6 8.10.7 +# manifest name: all +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--postgresql' 'sourcehut' 'psql.project' +# +# 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 +# +# REGENDATA ["--postgresql","sourcehut","psql.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-7.8.1 + - ghc-7.8.2 + - ghc-7.8.3 + - ghc-7.8.4 + - ghc-7.10.1 + - ghc-7.10.2 + - ghc-7.10.3 + - ghc-8.0.1 + - ghc-8.0.2 + - ghc-8.2.1 + - ghc-8.2.2 + - ghc-8.4.1 + - ghc-8.4.2 + - ghc-8.4.3 + - ghc-8.4.4 + - ghc-8.6.1 + - ghc-8.6.2 + - ghc-8.6.3 + - ghc-8.6.4 + - ghc-8.6.5 + - ghc-8.8.1 + - ghc-8.8.2 + - ghc-8.8.3 + - ghc-8.8.4 + - ghc-8.10.1 + - ghc-8.10.2 + - ghc-8.10.3 + - ghc-8.10.4 + - ghc-8.10.5 + - ghc-8.10.6 + - ghc-8.10.7 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 7_8_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.8.1 + - 7_8_1-check: | + cd example.org + cabal check + - 7_8_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_8_1-build: | + cd example.org + cabal build all + - 7_8_1-test: | + cd example.org + cabal test all --enable-tests + - 7_8_1-haddock: | + cd example.org + cabal haddock all + - 7_8_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.8.2 + - 7_8_2-check: | + cd example.org + cabal check + - 7_8_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_8_2-build: | + cd example.org + cabal build all + - 7_8_2-test: | + cd example.org + cabal test all --enable-tests + - 7_8_2-haddock: | + cd example.org + cabal haddock all + - 7_8_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.8.3 + - 7_8_3-check: | + cd example.org + cabal check + - 7_8_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_8_3-build: | + cd example.org + cabal build all + - 7_8_3-test: | + cd example.org + cabal test all --enable-tests + - 7_8_3-haddock: | + cd example.org + cabal haddock all + - 7_8_4-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.8.4 + - 7_8_4-check: | + cd example.org + cabal check + - 7_8_4-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_8_4-build: | + cd example.org + cabal build all + - 7_8_4-test: | + cd example.org + cabal test all --enable-tests + - 7_8_4-haddock: | + cd example.org + cabal haddock all + - 7_10_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.10.1 + - 7_10_1-check: | + cd example.org + cabal check + - 7_10_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_10_1-build: | + cd example.org + cabal build all + - 7_10_1-test: | + cd example.org + cabal test all --enable-tests + - 7_10_1-haddock: | + cd example.org + cabal haddock all + - 7_10_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.10.2 + - 7_10_2-check: | + cd example.org + cabal check + - 7_10_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_10_2-build: | + cd example.org + cabal build all + - 7_10_2-test: | + cd example.org + cabal test all --enable-tests + - 7_10_2-haddock: | + cd example.org + cabal haddock all + - 7_10_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.10.3 + - 7_10_3-check: | + cd example.org + cabal check + - 7_10_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_10_3-build: | + cd example.org + cabal build all + - 7_10_3-test: | + cd example.org + cabal test all --enable-tests + - 7_10_3-haddock: | + cd example.org + cabal haddock all + - 8_0_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.0.1 + - 8_0_1-check: | + cd example.org + cabal check + - 8_0_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_0_1-build: | + cd example.org + cabal build all + - 8_0_1-test: | + cd example.org + cabal test all --enable-tests + - 8_0_1-haddock: | + cd example.org + cabal haddock all + - 8_0_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.0.2 + - 8_0_2-check: | + cd example.org + cabal check + - 8_0_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_0_2-build: | + cd example.org + cabal build all + - 8_0_2-test: | + cd example.org + cabal test all --enable-tests + - 8_0_2-haddock: | + cd example.org + cabal haddock all + - 8_2_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.2.1 + - 8_2_1-check: | + cd example.org + cabal check + - 8_2_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_2_1-build: | + cd example.org + cabal build all + - 8_2_1-test: | + cd example.org + cabal test all --enable-tests + - 8_2_1-haddock: | + cd example.org + cabal haddock all + - 8_2_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.2.2 + - 8_2_2-check: | + cd example.org + cabal check + - 8_2_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_2_2-build: | + cd example.org + cabal build all + - 8_2_2-test: | + cd example.org + cabal test all --enable-tests + - 8_2_2-haddock: | + cd example.org + cabal haddock all + - 8_4_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.4.1 + - 8_4_1-check: | + cd example.org + cabal check + - 8_4_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_4_1-build: | + cd example.org + cabal build all + - 8_4_1-test: | + cd example.org + cabal test all --enable-tests + - 8_4_1-haddock: | + cd example.org + cabal haddock all + - 8_4_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.4.2 + - 8_4_2-check: | + cd example.org + cabal check + - 8_4_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_4_2-build: | + cd example.org + cabal build all + - 8_4_2-test: | + cd example.org + cabal test all --enable-tests + - 8_4_2-haddock: | + cd example.org + cabal haddock all + - 8_4_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.4.3 + - 8_4_3-check: | + cd example.org + cabal check + - 8_4_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_4_3-build: | + cd example.org + cabal build all + - 8_4_3-test: | + cd example.org + cabal test all --enable-tests + - 8_4_3-haddock: | + cd example.org + cabal haddock all + - 8_4_4-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.4.4 + - 8_4_4-check: | + cd example.org + cabal check + - 8_4_4-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_4_4-build: | + cd example.org + cabal build all + - 8_4_4-test: | + cd example.org + cabal test all --enable-tests + - 8_4_4-haddock: | + cd example.org + cabal haddock all + - 8_6_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.6.1 + - 8_6_1-check: | + cd example.org + cabal check + - 8_6_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_6_1-build: | + cd example.org + cabal build all + - 8_6_1-test: | + cd example.org + cabal test all --enable-tests + - 8_6_1-haddock: | + cd example.org + cabal haddock all + - 8_6_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.6.2 + - 8_6_2-check: | + cd example.org + cabal check + - 8_6_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_6_2-build: | + cd example.org + cabal build all + - 8_6_2-test: | + cd example.org + cabal test all --enable-tests + - 8_6_2-haddock: | + cd example.org + cabal haddock all + - 8_6_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.6.3 + - 8_6_3-check: | + cd example.org + cabal check + - 8_6_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_6_3-build: | + cd example.org + cabal build all + - 8_6_3-test: | + cd example.org + cabal test all --enable-tests + - 8_6_3-haddock: | + cd example.org + cabal haddock all + - 8_6_4-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.6.4 + - 8_6_4-check: | + cd example.org + cabal check + - 8_6_4-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_6_4-build: | + cd example.org + cabal build all + - 8_6_4-test: | + cd example.org + cabal test all --enable-tests + - 8_6_4-haddock: | + cd example.org + cabal haddock all + - 8_6_5-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.6.5 + - 8_6_5-check: | + cd example.org + cabal check + - 8_6_5-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_6_5-build: | + cd example.org + cabal build all + - 8_6_5-test: | + cd example.org + cabal test all --enable-tests + - 8_6_5-haddock: | + cd example.org + cabal haddock all + - 8_8_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.8.1 + - 8_8_1-check: | + cd example.org + cabal check + - 8_8_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_8_1-build: | + cd example.org + cabal build all + - 8_8_1-test: | + cd example.org + cabal test all --enable-tests + - 8_8_1-haddock: | + cd example.org + cabal haddock all + - 8_8_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.8.2 + - 8_8_2-check: | + cd example.org + cabal check + - 8_8_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_8_2-build: | + cd example.org + cabal build all + - 8_8_2-test: | + cd example.org + cabal test all --enable-tests + - 8_8_2-haddock: | + cd example.org + cabal haddock all + - 8_8_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.8.3 + - 8_8_3-check: | + cd example.org + cabal check + - 8_8_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_8_3-build: | + cd example.org + cabal build all + - 8_8_3-test: | + cd example.org + cabal test all --enable-tests + - 8_8_3-haddock: | + cd example.org + cabal haddock all + - 8_8_4-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.8.4 + - 8_8_4-check: | + cd example.org + cabal check + - 8_8_4-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_8_4-build: | + cd example.org + cabal build all + - 8_8_4-test: | + cd example.org + cabal test all --enable-tests + - 8_8_4-haddock: | + cd example.org + cabal haddock all + - 8_10_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.1 + - 8_10_1-check: | + cd example.org + cabal check + - 8_10_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_1-build: | + cd example.org + cabal build all + - 8_10_1-test: | + cd example.org + cabal test all --enable-tests + - 8_10_1-haddock: | + cd example.org + cabal haddock all + - 8_10_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.2 + - 8_10_2-check: | + cd example.org + cabal check + - 8_10_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_2-build: | + cd example.org + cabal build all + - 8_10_2-test: | + cd example.org + cabal test all --enable-tests + - 8_10_2-haddock: | + cd example.org + cabal haddock all + - 8_10_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.3 + - 8_10_3-check: | + cd example.org + cabal check + - 8_10_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_3-build: | + cd example.org + cabal build all + - 8_10_3-test: | + cd example.org + cabal test all --enable-tests + - 8_10_3-haddock: | + cd example.org + cabal haddock all + - 8_10_4-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.4 + - 8_10_4-check: | + cd example.org + cabal check + - 8_10_4-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_4-build: | + cd example.org + cabal build all + - 8_10_4-test: | + cd example.org + cabal test all --enable-tests + - 8_10_4-haddock: | + cd example.org + cabal haddock all + - 8_10_5-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.5 + - 8_10_5-check: | + cd example.org + cabal check + - 8_10_5-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_5-build: | + cd example.org + cabal build all + - 8_10_5-test: | + cd example.org + cabal test all --enable-tests + - 8_10_5-haddock: | + cd example.org + cabal haddock all + - 8_10_6-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.6 + - 8_10_6-check: | + cd example.org + cabal check + - 8_10_6-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_6-build: | + cd example.org + cabal build all + - 8_10_6-test: | + cd example.org + cabal test all --enable-tests + - 8_10_6-haddock: | + cd example.org + cabal haddock all + - 8_10_7-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.7 + - 8_10_7-check: | + cd example.org + cabal check + - 8_10_7-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_7-build: | + cd example.org + cabal build all + - 8_10_7-test: | + cd example.org + cabal test all --enable-tests + - 8_10_7-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com diff --git a/fixtures/psql.sourcehut-parallel b/fixtures/psql.sourcehut-parallel new file mode 100644 index 00000000..cc5d5312 --- /dev/null +++ b/fixtures/psql.sourcehut-parallel @@ -0,0 +1,1552 @@ +# SUCCESS +# *INFO* Generating Sourcehut config for testing for GHC versions: 7.8.1 7.8.2 7.8.3 7.8.4 7.10.1 7.10.2 7.10.3 8.0.1 8.0.2 8.2.1 8.2.2 8.4.1 8.4.2 8.4.3 8.4.4 8.6.1 8.6.2 8.6.3 8.6.4 8.6.5 8.8.1 8.8.2 8.8.3 8.8.4 8.10.1 8.10.2 8.10.3 8.10.4 8.10.5 8.10.6 8.10.7 +# manifest name: 7.10.1 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--postgresql' 'sourcehut' 'psql.project' +# +# 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 +# +# REGENDATA ["--postgresql","sourcehut","psql.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-7.10.1 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 7_10_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.10.1 + - 7_10_1-check: | + cd example.org + cabal check + - 7_10_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_10_1-build: | + cd example.org + cabal build all + - 7_10_1-test: | + cd example.org + cabal test all --enable-tests + - 7_10_1-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 7.10.2 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--postgresql' 'sourcehut' 'psql.project' +# +# 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 +# +# REGENDATA ["--postgresql","sourcehut","psql.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-7.10.2 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 7_10_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.10.2 + - 7_10_2-check: | + cd example.org + cabal check + - 7_10_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_10_2-build: | + cd example.org + cabal build all + - 7_10_2-test: | + cd example.org + cabal test all --enable-tests + - 7_10_2-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 7.10.3 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--postgresql' 'sourcehut' 'psql.project' +# +# 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 +# +# REGENDATA ["--postgresql","sourcehut","psql.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-7.10.3 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 7_10_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.10.3 + - 7_10_3-check: | + cd example.org + cabal check + - 7_10_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_10_3-build: | + cd example.org + cabal build all + - 7_10_3-test: | + cd example.org + cabal test all --enable-tests + - 7_10_3-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 7.8.1 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--postgresql' 'sourcehut' 'psql.project' +# +# 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 +# +# REGENDATA ["--postgresql","sourcehut","psql.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-7.8.1 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 7_8_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.8.1 + - 7_8_1-check: | + cd example.org + cabal check + - 7_8_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_8_1-build: | + cd example.org + cabal build all + - 7_8_1-test: | + cd example.org + cabal test all --enable-tests + - 7_8_1-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 7.8.2 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--postgresql' 'sourcehut' 'psql.project' +# +# 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 +# +# REGENDATA ["--postgresql","sourcehut","psql.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-7.8.2 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 7_8_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.8.2 + - 7_8_2-check: | + cd example.org + cabal check + - 7_8_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_8_2-build: | + cd example.org + cabal build all + - 7_8_2-test: | + cd example.org + cabal test all --enable-tests + - 7_8_2-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 7.8.3 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--postgresql' 'sourcehut' 'psql.project' +# +# 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 +# +# REGENDATA ["--postgresql","sourcehut","psql.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-7.8.3 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 7_8_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.8.3 + - 7_8_3-check: | + cd example.org + cabal check + - 7_8_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_8_3-build: | + cd example.org + cabal build all + - 7_8_3-test: | + cd example.org + cabal test all --enable-tests + - 7_8_3-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 7.8.4 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--postgresql' 'sourcehut' 'psql.project' +# +# 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 +# +# REGENDATA ["--postgresql","sourcehut","psql.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-7.8.4 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 7_8_4-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.8.4 + - 7_8_4-check: | + cd example.org + cabal check + - 7_8_4-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_8_4-build: | + cd example.org + cabal build all + - 7_8_4-test: | + cd example.org + cabal test all --enable-tests + - 7_8_4-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.0.1 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--postgresql' 'sourcehut' 'psql.project' +# +# 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 +# +# REGENDATA ["--postgresql","sourcehut","psql.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.0.1 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_0_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.0.1 + - 8_0_1-check: | + cd example.org + cabal check + - 8_0_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_0_1-build: | + cd example.org + cabal build all + - 8_0_1-test: | + cd example.org + cabal test all --enable-tests + - 8_0_1-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.0.2 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--postgresql' 'sourcehut' 'psql.project' +# +# 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 +# +# REGENDATA ["--postgresql","sourcehut","psql.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.0.2 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_0_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.0.2 + - 8_0_2-check: | + cd example.org + cabal check + - 8_0_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_0_2-build: | + cd example.org + cabal build all + - 8_0_2-test: | + cd example.org + cabal test all --enable-tests + - 8_0_2-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.10.1 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--postgresql' 'sourcehut' 'psql.project' +# +# 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 +# +# REGENDATA ["--postgresql","sourcehut","psql.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.10.1 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_10_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.1 + - 8_10_1-check: | + cd example.org + cabal check + - 8_10_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_1-build: | + cd example.org + cabal build all + - 8_10_1-test: | + cd example.org + cabal test all --enable-tests + - 8_10_1-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.10.2 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--postgresql' 'sourcehut' 'psql.project' +# +# 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 +# +# REGENDATA ["--postgresql","sourcehut","psql.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.10.2 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_10_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.2 + - 8_10_2-check: | + cd example.org + cabal check + - 8_10_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_2-build: | + cd example.org + cabal build all + - 8_10_2-test: | + cd example.org + cabal test all --enable-tests + - 8_10_2-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.10.3 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--postgresql' 'sourcehut' 'psql.project' +# +# 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 +# +# REGENDATA ["--postgresql","sourcehut","psql.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.10.3 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_10_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.3 + - 8_10_3-check: | + cd example.org + cabal check + - 8_10_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_3-build: | + cd example.org + cabal build all + - 8_10_3-test: | + cd example.org + cabal test all --enable-tests + - 8_10_3-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.10.4 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--postgresql' 'sourcehut' 'psql.project' +# +# 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 +# +# REGENDATA ["--postgresql","sourcehut","psql.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.10.4 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_10_4-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.4 + - 8_10_4-check: | + cd example.org + cabal check + - 8_10_4-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_4-build: | + cd example.org + cabal build all + - 8_10_4-test: | + cd example.org + cabal test all --enable-tests + - 8_10_4-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.10.5 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--postgresql' 'sourcehut' 'psql.project' +# +# 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 +# +# REGENDATA ["--postgresql","sourcehut","psql.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.10.5 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_10_5-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.5 + - 8_10_5-check: | + cd example.org + cabal check + - 8_10_5-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_5-build: | + cd example.org + cabal build all + - 8_10_5-test: | + cd example.org + cabal test all --enable-tests + - 8_10_5-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.10.6 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--postgresql' 'sourcehut' 'psql.project' +# +# 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 +# +# REGENDATA ["--postgresql","sourcehut","psql.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.10.6 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_10_6-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.6 + - 8_10_6-check: | + cd example.org + cabal check + - 8_10_6-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_6-build: | + cd example.org + cabal build all + - 8_10_6-test: | + cd example.org + cabal test all --enable-tests + - 8_10_6-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.10.7 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--postgresql' 'sourcehut' 'psql.project' +# +# 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 +# +# REGENDATA ["--postgresql","sourcehut","psql.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.10.7 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_10_7-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.7 + - 8_10_7-check: | + cd example.org + cabal check + - 8_10_7-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_7-build: | + cd example.org + cabal build all + - 8_10_7-test: | + cd example.org + cabal test all --enable-tests + - 8_10_7-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.2.1 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--postgresql' 'sourcehut' 'psql.project' +# +# 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 +# +# REGENDATA ["--postgresql","sourcehut","psql.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.2.1 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_2_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.2.1 + - 8_2_1-check: | + cd example.org + cabal check + - 8_2_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_2_1-build: | + cd example.org + cabal build all + - 8_2_1-test: | + cd example.org + cabal test all --enable-tests + - 8_2_1-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.2.2 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--postgresql' 'sourcehut' 'psql.project' +# +# 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 +# +# REGENDATA ["--postgresql","sourcehut","psql.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.2.2 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_2_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.2.2 + - 8_2_2-check: | + cd example.org + cabal check + - 8_2_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_2_2-build: | + cd example.org + cabal build all + - 8_2_2-test: | + cd example.org + cabal test all --enable-tests + - 8_2_2-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.4.1 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--postgresql' 'sourcehut' 'psql.project' +# +# 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 +# +# REGENDATA ["--postgresql","sourcehut","psql.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.4.1 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_4_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.4.1 + - 8_4_1-check: | + cd example.org + cabal check + - 8_4_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_4_1-build: | + cd example.org + cabal build all + - 8_4_1-test: | + cd example.org + cabal test all --enable-tests + - 8_4_1-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.4.2 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--postgresql' 'sourcehut' 'psql.project' +# +# 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 +# +# REGENDATA ["--postgresql","sourcehut","psql.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.4.2 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_4_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.4.2 + - 8_4_2-check: | + cd example.org + cabal check + - 8_4_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_4_2-build: | + cd example.org + cabal build all + - 8_4_2-test: | + cd example.org + cabal test all --enable-tests + - 8_4_2-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.4.3 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--postgresql' 'sourcehut' 'psql.project' +# +# 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 +# +# REGENDATA ["--postgresql","sourcehut","psql.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.4.3 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_4_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.4.3 + - 8_4_3-check: | + cd example.org + cabal check + - 8_4_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_4_3-build: | + cd example.org + cabal build all + - 8_4_3-test: | + cd example.org + cabal test all --enable-tests + - 8_4_3-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.4.4 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--postgresql' 'sourcehut' 'psql.project' +# +# 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 +# +# REGENDATA ["--postgresql","sourcehut","psql.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.4.4 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_4_4-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.4.4 + - 8_4_4-check: | + cd example.org + cabal check + - 8_4_4-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_4_4-build: | + cd example.org + cabal build all + - 8_4_4-test: | + cd example.org + cabal test all --enable-tests + - 8_4_4-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.6.1 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--postgresql' 'sourcehut' 'psql.project' +# +# 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 +# +# REGENDATA ["--postgresql","sourcehut","psql.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.6.1 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_6_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.6.1 + - 8_6_1-check: | + cd example.org + cabal check + - 8_6_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_6_1-build: | + cd example.org + cabal build all + - 8_6_1-test: | + cd example.org + cabal test all --enable-tests + - 8_6_1-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.6.2 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--postgresql' 'sourcehut' 'psql.project' +# +# 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 +# +# REGENDATA ["--postgresql","sourcehut","psql.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.6.2 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_6_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.6.2 + - 8_6_2-check: | + cd example.org + cabal check + - 8_6_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_6_2-build: | + cd example.org + cabal build all + - 8_6_2-test: | + cd example.org + cabal test all --enable-tests + - 8_6_2-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.6.3 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--postgresql' 'sourcehut' 'psql.project' +# +# 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 +# +# REGENDATA ["--postgresql","sourcehut","psql.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.6.3 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_6_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.6.3 + - 8_6_3-check: | + cd example.org + cabal check + - 8_6_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_6_3-build: | + cd example.org + cabal build all + - 8_6_3-test: | + cd example.org + cabal test all --enable-tests + - 8_6_3-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.6.4 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--postgresql' 'sourcehut' 'psql.project' +# +# 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 +# +# REGENDATA ["--postgresql","sourcehut","psql.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.6.4 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_6_4-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.6.4 + - 8_6_4-check: | + cd example.org + cabal check + - 8_6_4-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_6_4-build: | + cd example.org + cabal build all + - 8_6_4-test: | + cd example.org + cabal test all --enable-tests + - 8_6_4-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.6.5 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--postgresql' 'sourcehut' 'psql.project' +# +# 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 +# +# REGENDATA ["--postgresql","sourcehut","psql.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.6.5 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_6_5-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.6.5 + - 8_6_5-check: | + cd example.org + cabal check + - 8_6_5-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_6_5-build: | + cd example.org + cabal build all + - 8_6_5-test: | + cd example.org + cabal test all --enable-tests + - 8_6_5-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.8.1 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--postgresql' 'sourcehut' 'psql.project' +# +# 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 +# +# REGENDATA ["--postgresql","sourcehut","psql.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.8.1 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_8_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.8.1 + - 8_8_1-check: | + cd example.org + cabal check + - 8_8_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_8_1-build: | + cd example.org + cabal build all + - 8_8_1-test: | + cd example.org + cabal test all --enable-tests + - 8_8_1-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.8.2 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--postgresql' 'sourcehut' 'psql.project' +# +# 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 +# +# REGENDATA ["--postgresql","sourcehut","psql.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.8.2 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_8_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.8.2 + - 8_8_2-check: | + cd example.org + cabal check + - 8_8_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_8_2-build: | + cd example.org + cabal build all + - 8_8_2-test: | + cd example.org + cabal test all --enable-tests + - 8_8_2-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.8.3 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--postgresql' 'sourcehut' 'psql.project' +# +# 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 +# +# REGENDATA ["--postgresql","sourcehut","psql.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.8.3 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_8_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.8.3 + - 8_8_3-check: | + cd example.org + cabal check + - 8_8_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_8_3-build: | + cd example.org + cabal build all + - 8_8_3-test: | + cd example.org + cabal test all --enable-tests + - 8_8_3-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.8.4 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--postgresql' 'sourcehut' 'psql.project' +# +# 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 +# +# REGENDATA ["--postgresql","sourcehut","psql.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.8.4 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_8_4-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.8.4 + - 8_8_4-check: | + cd example.org + cabal check + - 8_8_4-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_8_4-build: | + cd example.org + cabal build all + - 8_8_4-test: | + cd example.org + cabal test all --enable-tests + - 8_8_4-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com diff --git a/fixtures/travis-patch.sourcehut b/fixtures/travis-patch.sourcehut new file mode 100644 index 00000000..9f7768d2 --- /dev/null +++ b/fixtures/travis-patch.sourcehut @@ -0,0 +1,652 @@ +# SUCCESS +# *INFO* Generating Sourcehut config for testing for GHC versions: 7.8.1 7.8.2 7.8.3 7.8.4 7.10.1 7.10.2 7.10.3 8.0.1 8.0.2 8.2.1 8.2.2 8.4.1 8.4.2 8.4.3 8.4.4 8.6.1 8.6.2 8.6.3 8.6.4 8.6.5 8.8.1 8.8.2 8.8.3 8.8.4 8.10.1 8.10.2 8.10.3 8.10.4 8.10.5 8.10.6 8.10.7 +# manifest name: all +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--travis-patches=travis-patch.patch' 'sourcehut' 'travis-patch.project' +# +# 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 +# +# REGENDATA ["--travis-patches=travis-patch.patch","sourcehut","travis-patch.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-7.8.1 + - ghc-7.8.2 + - ghc-7.8.3 + - ghc-7.8.4 + - ghc-7.10.1 + - ghc-7.10.2 + - ghc-7.10.3 + - ghc-8.0.1 + - ghc-8.0.2 + - ghc-8.2.1 + - ghc-8.2.2 + - ghc-8.4.1 + - ghc-8.4.2 + - ghc-8.4.3 + - ghc-8.4.4 + - ghc-8.6.1 + - ghc-8.6.2 + - ghc-8.6.3 + - ghc-8.6.4 + - ghc-8.6.5 + - ghc-8.8.1 + - ghc-8.8.2 + - ghc-8.8.3 + - ghc-8.8.4 + - ghc-8.10.1 + - ghc-8.10.2 + - ghc-8.10.3 + - ghc-8.10.4 + - ghc-8.10.5 + - ghc-8.10.6 + - ghc-8.10.7 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 7_8_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.8.1 + - 7_8_1-check: | + cd example.org + cabal check + - 7_8_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_8_1-build: | + cd example.org + cabal build all + - 7_8_1-test: | + cd example.org + cabal test all --enable-tests + - 7_8_1-haddock: | + cd example.org + cabal haddock all + - 7_8_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.8.2 + - 7_8_2-check: | + cd example.org + cabal check + - 7_8_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_8_2-build: | + cd example.org + cabal build all + - 7_8_2-test: | + cd example.org + cabal test all --enable-tests + - 7_8_2-haddock: | + cd example.org + cabal haddock all + - 7_8_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.8.3 + - 7_8_3-check: | + cd example.org + cabal check + - 7_8_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_8_3-build: | + cd example.org + cabal build all + - 7_8_3-test: | + cd example.org + cabal test all --enable-tests + - 7_8_3-haddock: | + cd example.org + cabal haddock all + - 7_8_4-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.8.4 + - 7_8_4-check: | + cd example.org + cabal check + - 7_8_4-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_8_4-build: | + cd example.org + cabal build all + - 7_8_4-test: | + cd example.org + cabal test all --enable-tests + - 7_8_4-haddock: | + cd example.org + cabal haddock all + - 7_10_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.10.1 + - 7_10_1-check: | + cd example.org + cabal check + - 7_10_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_10_1-build: | + cd example.org + cabal build all + - 7_10_1-test: | + cd example.org + cabal test all --enable-tests + - 7_10_1-haddock: | + cd example.org + cabal haddock all + - 7_10_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.10.2 + - 7_10_2-check: | + cd example.org + cabal check + - 7_10_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_10_2-build: | + cd example.org + cabal build all + - 7_10_2-test: | + cd example.org + cabal test all --enable-tests + - 7_10_2-haddock: | + cd example.org + cabal haddock all + - 7_10_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.10.3 + - 7_10_3-check: | + cd example.org + cabal check + - 7_10_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_10_3-build: | + cd example.org + cabal build all + - 7_10_3-test: | + cd example.org + cabal test all --enable-tests + - 7_10_3-haddock: | + cd example.org + cabal haddock all + - 8_0_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.0.1 + - 8_0_1-check: | + cd example.org + cabal check + - 8_0_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_0_1-build: | + cd example.org + cabal build all + - 8_0_1-test: | + cd example.org + cabal test all --enable-tests + - 8_0_1-haddock: | + cd example.org + cabal haddock all + - 8_0_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.0.2 + - 8_0_2-check: | + cd example.org + cabal check + - 8_0_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_0_2-build: | + cd example.org + cabal build all + - 8_0_2-test: | + cd example.org + cabal test all --enable-tests + - 8_0_2-haddock: | + cd example.org + cabal haddock all + - 8_2_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.2.1 + - 8_2_1-check: | + cd example.org + cabal check + - 8_2_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_2_1-build: | + cd example.org + cabal build all + - 8_2_1-test: | + cd example.org + cabal test all --enable-tests + - 8_2_1-haddock: | + cd example.org + cabal haddock all + - 8_2_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.2.2 + - 8_2_2-check: | + cd example.org + cabal check + - 8_2_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_2_2-build: | + cd example.org + cabal build all + - 8_2_2-test: | + cd example.org + cabal test all --enable-tests + - 8_2_2-haddock: | + cd example.org + cabal haddock all + - 8_4_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.4.1 + - 8_4_1-check: | + cd example.org + cabal check + - 8_4_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_4_1-build: | + cd example.org + cabal build all + - 8_4_1-test: | + cd example.org + cabal test all --enable-tests + - 8_4_1-haddock: | + cd example.org + cabal haddock all + - 8_4_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.4.2 + - 8_4_2-check: | + cd example.org + cabal check + - 8_4_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_4_2-build: | + cd example.org + cabal build all + - 8_4_2-test: | + cd example.org + cabal test all --enable-tests + - 8_4_2-haddock: | + cd example.org + cabal haddock all + - 8_4_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.4.3 + - 8_4_3-check: | + cd example.org + cabal check + - 8_4_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_4_3-build: | + cd example.org + cabal build all + - 8_4_3-test: | + cd example.org + cabal test all --enable-tests + - 8_4_3-haddock: | + cd example.org + cabal haddock all + - 8_4_4-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.4.4 + - 8_4_4-check: | + cd example.org + cabal check + - 8_4_4-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_4_4-build: | + cd example.org + cabal build all + - 8_4_4-test: | + cd example.org + cabal test all --enable-tests + - 8_4_4-haddock: | + cd example.org + cabal haddock all + - 8_6_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.6.1 + - 8_6_1-check: | + cd example.org + cabal check + - 8_6_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_6_1-build: | + cd example.org + cabal build all + - 8_6_1-test: | + cd example.org + cabal test all --enable-tests + - 8_6_1-haddock: | + cd example.org + cabal haddock all + - 8_6_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.6.2 + - 8_6_2-check: | + cd example.org + cabal check + - 8_6_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_6_2-build: | + cd example.org + cabal build all + - 8_6_2-test: | + cd example.org + cabal test all --enable-tests + - 8_6_2-haddock: | + cd example.org + cabal haddock all + - 8_6_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.6.3 + - 8_6_3-check: | + cd example.org + cabal check + - 8_6_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_6_3-build: | + cd example.org + cabal build all + - 8_6_3-test: | + cd example.org + cabal test all --enable-tests + - 8_6_3-haddock: | + cd example.org + cabal haddock all + - 8_6_4-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.6.4 + - 8_6_4-check: | + cd example.org + cabal check + - 8_6_4-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_6_4-build: | + cd example.org + cabal build all + - 8_6_4-test: | + cd example.org + cabal test all --enable-tests + - 8_6_4-haddock: | + cd example.org + cabal haddock all + - 8_6_5-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.6.5 + - 8_6_5-check: | + cd example.org + cabal check + - 8_6_5-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_6_5-build: | + cd example.org + cabal build all + - 8_6_5-test: | + cd example.org + cabal test all --enable-tests + - 8_6_5-haddock: | + cd example.org + cabal haddock all + - 8_8_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.8.1 + - 8_8_1-check: | + cd example.org + cabal check + - 8_8_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_8_1-build: | + cd example.org + cabal build all + - 8_8_1-test: | + cd example.org + cabal test all --enable-tests + - 8_8_1-haddock: | + cd example.org + cabal haddock all + - 8_8_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.8.2 + - 8_8_2-check: | + cd example.org + cabal check + - 8_8_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_8_2-build: | + cd example.org + cabal build all + - 8_8_2-test: | + cd example.org + cabal test all --enable-tests + - 8_8_2-haddock: | + cd example.org + cabal haddock all + - 8_8_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.8.3 + - 8_8_3-check: | + cd example.org + cabal check + - 8_8_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_8_3-build: | + cd example.org + cabal build all + - 8_8_3-test: | + cd example.org + cabal test all --enable-tests + - 8_8_3-haddock: | + cd example.org + cabal haddock all + - 8_8_4-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.8.4 + - 8_8_4-check: | + cd example.org + cabal check + - 8_8_4-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_8_4-build: | + cd example.org + cabal build all + - 8_8_4-test: | + cd example.org + cabal test all --enable-tests + - 8_8_4-haddock: | + cd example.org + cabal haddock all + - 8_10_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.1 + - 8_10_1-check: | + cd example.org + cabal check + - 8_10_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_1-build: | + cd example.org + cabal build all + - 8_10_1-test: | + cd example.org + cabal test all --enable-tests + - 8_10_1-haddock: | + cd example.org + cabal haddock all + - 8_10_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.2 + - 8_10_2-check: | + cd example.org + cabal check + - 8_10_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_2-build: | + cd example.org + cabal build all + - 8_10_2-test: | + cd example.org + cabal test all --enable-tests + - 8_10_2-haddock: | + cd example.org + cabal haddock all + - 8_10_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.3 + - 8_10_3-check: | + cd example.org + cabal check + - 8_10_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_3-build: | + cd example.org + cabal build all + - 8_10_3-test: | + cd example.org + cabal test all --enable-tests + - 8_10_3-haddock: | + cd example.org + cabal haddock all + - 8_10_4-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.4 + - 8_10_4-check: | + cd example.org + cabal check + - 8_10_4-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_4-build: | + cd example.org + cabal build all + - 8_10_4-test: | + cd example.org + cabal test all --enable-tests + - 8_10_4-haddock: | + cd example.org + cabal haddock all + - 8_10_5-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.5 + - 8_10_5-check: | + cd example.org + cabal check + - 8_10_5-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_5-build: | + cd example.org + cabal build all + - 8_10_5-test: | + cd example.org + cabal test all --enable-tests + - 8_10_5-haddock: | + cd example.org + cabal haddock all + - 8_10_6-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.6 + - 8_10_6-check: | + cd example.org + cabal check + - 8_10_6-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_6-build: | + cd example.org + cabal build all + - 8_10_6-test: | + cd example.org + cabal test all --enable-tests + - 8_10_6-haddock: | + cd example.org + cabal haddock all + - 8_10_7-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.7 + - 8_10_7-check: | + cd example.org + cabal check + - 8_10_7-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_7-build: | + cd example.org + cabal build all + - 8_10_7-test: | + cd example.org + cabal test all --enable-tests + - 8_10_7-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com diff --git a/fixtures/travis-patch.sourcehut-parallel b/fixtures/travis-patch.sourcehut-parallel new file mode 100644 index 00000000..e0d309e9 --- /dev/null +++ b/fixtures/travis-patch.sourcehut-parallel @@ -0,0 +1,1552 @@ +# SUCCESS +# *INFO* Generating Sourcehut config for testing for GHC versions: 7.8.1 7.8.2 7.8.3 7.8.4 7.10.1 7.10.2 7.10.3 8.0.1 8.0.2 8.2.1 8.2.2 8.4.1 8.4.2 8.4.3 8.4.4 8.6.1 8.6.2 8.6.3 8.6.4 8.6.5 8.8.1 8.8.2 8.8.3 8.8.4 8.10.1 8.10.2 8.10.3 8.10.4 8.10.5 8.10.6 8.10.7 +# manifest name: 7.10.1 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--travis-patches=travis-patch.patch' 'sourcehut' 'travis-patch.project' +# +# 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 +# +# REGENDATA ["--travis-patches=travis-patch.patch","sourcehut","travis-patch.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-7.10.1 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 7_10_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.10.1 + - 7_10_1-check: | + cd example.org + cabal check + - 7_10_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_10_1-build: | + cd example.org + cabal build all + - 7_10_1-test: | + cd example.org + cabal test all --enable-tests + - 7_10_1-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 7.10.2 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--travis-patches=travis-patch.patch' 'sourcehut' 'travis-patch.project' +# +# 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 +# +# REGENDATA ["--travis-patches=travis-patch.patch","sourcehut","travis-patch.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-7.10.2 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 7_10_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.10.2 + - 7_10_2-check: | + cd example.org + cabal check + - 7_10_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_10_2-build: | + cd example.org + cabal build all + - 7_10_2-test: | + cd example.org + cabal test all --enable-tests + - 7_10_2-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 7.10.3 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--travis-patches=travis-patch.patch' 'sourcehut' 'travis-patch.project' +# +# 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 +# +# REGENDATA ["--travis-patches=travis-patch.patch","sourcehut","travis-patch.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-7.10.3 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 7_10_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.10.3 + - 7_10_3-check: | + cd example.org + cabal check + - 7_10_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_10_3-build: | + cd example.org + cabal build all + - 7_10_3-test: | + cd example.org + cabal test all --enable-tests + - 7_10_3-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 7.8.1 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--travis-patches=travis-patch.patch' 'sourcehut' 'travis-patch.project' +# +# 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 +# +# REGENDATA ["--travis-patches=travis-patch.patch","sourcehut","travis-patch.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-7.8.1 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 7_8_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.8.1 + - 7_8_1-check: | + cd example.org + cabal check + - 7_8_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_8_1-build: | + cd example.org + cabal build all + - 7_8_1-test: | + cd example.org + cabal test all --enable-tests + - 7_8_1-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 7.8.2 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--travis-patches=travis-patch.patch' 'sourcehut' 'travis-patch.project' +# +# 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 +# +# REGENDATA ["--travis-patches=travis-patch.patch","sourcehut","travis-patch.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-7.8.2 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 7_8_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.8.2 + - 7_8_2-check: | + cd example.org + cabal check + - 7_8_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_8_2-build: | + cd example.org + cabal build all + - 7_8_2-test: | + cd example.org + cabal test all --enable-tests + - 7_8_2-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 7.8.3 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--travis-patches=travis-patch.patch' 'sourcehut' 'travis-patch.project' +# +# 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 +# +# REGENDATA ["--travis-patches=travis-patch.patch","sourcehut","travis-patch.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-7.8.3 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 7_8_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.8.3 + - 7_8_3-check: | + cd example.org + cabal check + - 7_8_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_8_3-build: | + cd example.org + cabal build all + - 7_8_3-test: | + cd example.org + cabal test all --enable-tests + - 7_8_3-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 7.8.4 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--travis-patches=travis-patch.patch' 'sourcehut' 'travis-patch.project' +# +# 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 +# +# REGENDATA ["--travis-patches=travis-patch.patch","sourcehut","travis-patch.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-7.8.4 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 7_8_4-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.8.4 + - 7_8_4-check: | + cd example.org + cabal check + - 7_8_4-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_8_4-build: | + cd example.org + cabal build all + - 7_8_4-test: | + cd example.org + cabal test all --enable-tests + - 7_8_4-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.0.1 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--travis-patches=travis-patch.patch' 'sourcehut' 'travis-patch.project' +# +# 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 +# +# REGENDATA ["--travis-patches=travis-patch.patch","sourcehut","travis-patch.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.0.1 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_0_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.0.1 + - 8_0_1-check: | + cd example.org + cabal check + - 8_0_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_0_1-build: | + cd example.org + cabal build all + - 8_0_1-test: | + cd example.org + cabal test all --enable-tests + - 8_0_1-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.0.2 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--travis-patches=travis-patch.patch' 'sourcehut' 'travis-patch.project' +# +# 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 +# +# REGENDATA ["--travis-patches=travis-patch.patch","sourcehut","travis-patch.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.0.2 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_0_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.0.2 + - 8_0_2-check: | + cd example.org + cabal check + - 8_0_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_0_2-build: | + cd example.org + cabal build all + - 8_0_2-test: | + cd example.org + cabal test all --enable-tests + - 8_0_2-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.10.1 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--travis-patches=travis-patch.patch' 'sourcehut' 'travis-patch.project' +# +# 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 +# +# REGENDATA ["--travis-patches=travis-patch.patch","sourcehut","travis-patch.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.10.1 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_10_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.1 + - 8_10_1-check: | + cd example.org + cabal check + - 8_10_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_1-build: | + cd example.org + cabal build all + - 8_10_1-test: | + cd example.org + cabal test all --enable-tests + - 8_10_1-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.10.2 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--travis-patches=travis-patch.patch' 'sourcehut' 'travis-patch.project' +# +# 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 +# +# REGENDATA ["--travis-patches=travis-patch.patch","sourcehut","travis-patch.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.10.2 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_10_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.2 + - 8_10_2-check: | + cd example.org + cabal check + - 8_10_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_2-build: | + cd example.org + cabal build all + - 8_10_2-test: | + cd example.org + cabal test all --enable-tests + - 8_10_2-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.10.3 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--travis-patches=travis-patch.patch' 'sourcehut' 'travis-patch.project' +# +# 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 +# +# REGENDATA ["--travis-patches=travis-patch.patch","sourcehut","travis-patch.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.10.3 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_10_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.3 + - 8_10_3-check: | + cd example.org + cabal check + - 8_10_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_3-build: | + cd example.org + cabal build all + - 8_10_3-test: | + cd example.org + cabal test all --enable-tests + - 8_10_3-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.10.4 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--travis-patches=travis-patch.patch' 'sourcehut' 'travis-patch.project' +# +# 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 +# +# REGENDATA ["--travis-patches=travis-patch.patch","sourcehut","travis-patch.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.10.4 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_10_4-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.4 + - 8_10_4-check: | + cd example.org + cabal check + - 8_10_4-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_4-build: | + cd example.org + cabal build all + - 8_10_4-test: | + cd example.org + cabal test all --enable-tests + - 8_10_4-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.10.5 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--travis-patches=travis-patch.patch' 'sourcehut' 'travis-patch.project' +# +# 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 +# +# REGENDATA ["--travis-patches=travis-patch.patch","sourcehut","travis-patch.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.10.5 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_10_5-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.5 + - 8_10_5-check: | + cd example.org + cabal check + - 8_10_5-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_5-build: | + cd example.org + cabal build all + - 8_10_5-test: | + cd example.org + cabal test all --enable-tests + - 8_10_5-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.10.6 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--travis-patches=travis-patch.patch' 'sourcehut' 'travis-patch.project' +# +# 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 +# +# REGENDATA ["--travis-patches=travis-patch.patch","sourcehut","travis-patch.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.10.6 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_10_6-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.6 + - 8_10_6-check: | + cd example.org + cabal check + - 8_10_6-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_6-build: | + cd example.org + cabal build all + - 8_10_6-test: | + cd example.org + cabal test all --enable-tests + - 8_10_6-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.10.7 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--travis-patches=travis-patch.patch' 'sourcehut' 'travis-patch.project' +# +# 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 +# +# REGENDATA ["--travis-patches=travis-patch.patch","sourcehut","travis-patch.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.10.7 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_10_7-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.7 + - 8_10_7-check: | + cd example.org + cabal check + - 8_10_7-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_7-build: | + cd example.org + cabal build all + - 8_10_7-test: | + cd example.org + cabal test all --enable-tests + - 8_10_7-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.2.1 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--travis-patches=travis-patch.patch' 'sourcehut' 'travis-patch.project' +# +# 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 +# +# REGENDATA ["--travis-patches=travis-patch.patch","sourcehut","travis-patch.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.2.1 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_2_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.2.1 + - 8_2_1-check: | + cd example.org + cabal check + - 8_2_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_2_1-build: | + cd example.org + cabal build all + - 8_2_1-test: | + cd example.org + cabal test all --enable-tests + - 8_2_1-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.2.2 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--travis-patches=travis-patch.patch' 'sourcehut' 'travis-patch.project' +# +# 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 +# +# REGENDATA ["--travis-patches=travis-patch.patch","sourcehut","travis-patch.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.2.2 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_2_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.2.2 + - 8_2_2-check: | + cd example.org + cabal check + - 8_2_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_2_2-build: | + cd example.org + cabal build all + - 8_2_2-test: | + cd example.org + cabal test all --enable-tests + - 8_2_2-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.4.1 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--travis-patches=travis-patch.patch' 'sourcehut' 'travis-patch.project' +# +# 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 +# +# REGENDATA ["--travis-patches=travis-patch.patch","sourcehut","travis-patch.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.4.1 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_4_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.4.1 + - 8_4_1-check: | + cd example.org + cabal check + - 8_4_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_4_1-build: | + cd example.org + cabal build all + - 8_4_1-test: | + cd example.org + cabal test all --enable-tests + - 8_4_1-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.4.2 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--travis-patches=travis-patch.patch' 'sourcehut' 'travis-patch.project' +# +# 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 +# +# REGENDATA ["--travis-patches=travis-patch.patch","sourcehut","travis-patch.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.4.2 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_4_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.4.2 + - 8_4_2-check: | + cd example.org + cabal check + - 8_4_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_4_2-build: | + cd example.org + cabal build all + - 8_4_2-test: | + cd example.org + cabal test all --enable-tests + - 8_4_2-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.4.3 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--travis-patches=travis-patch.patch' 'sourcehut' 'travis-patch.project' +# +# 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 +# +# REGENDATA ["--travis-patches=travis-patch.patch","sourcehut","travis-patch.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.4.3 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_4_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.4.3 + - 8_4_3-check: | + cd example.org + cabal check + - 8_4_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_4_3-build: | + cd example.org + cabal build all + - 8_4_3-test: | + cd example.org + cabal test all --enable-tests + - 8_4_3-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.4.4 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--travis-patches=travis-patch.patch' 'sourcehut' 'travis-patch.project' +# +# 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 +# +# REGENDATA ["--travis-patches=travis-patch.patch","sourcehut","travis-patch.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.4.4 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_4_4-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.4.4 + - 8_4_4-check: | + cd example.org + cabal check + - 8_4_4-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_4_4-build: | + cd example.org + cabal build all + - 8_4_4-test: | + cd example.org + cabal test all --enable-tests + - 8_4_4-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.6.1 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--travis-patches=travis-patch.patch' 'sourcehut' 'travis-patch.project' +# +# 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 +# +# REGENDATA ["--travis-patches=travis-patch.patch","sourcehut","travis-patch.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.6.1 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_6_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.6.1 + - 8_6_1-check: | + cd example.org + cabal check + - 8_6_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_6_1-build: | + cd example.org + cabal build all + - 8_6_1-test: | + cd example.org + cabal test all --enable-tests + - 8_6_1-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.6.2 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--travis-patches=travis-patch.patch' 'sourcehut' 'travis-patch.project' +# +# 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 +# +# REGENDATA ["--travis-patches=travis-patch.patch","sourcehut","travis-patch.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.6.2 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_6_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.6.2 + - 8_6_2-check: | + cd example.org + cabal check + - 8_6_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_6_2-build: | + cd example.org + cabal build all + - 8_6_2-test: | + cd example.org + cabal test all --enable-tests + - 8_6_2-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.6.3 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--travis-patches=travis-patch.patch' 'sourcehut' 'travis-patch.project' +# +# 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 +# +# REGENDATA ["--travis-patches=travis-patch.patch","sourcehut","travis-patch.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.6.3 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_6_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.6.3 + - 8_6_3-check: | + cd example.org + cabal check + - 8_6_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_6_3-build: | + cd example.org + cabal build all + - 8_6_3-test: | + cd example.org + cabal test all --enable-tests + - 8_6_3-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.6.4 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--travis-patches=travis-patch.patch' 'sourcehut' 'travis-patch.project' +# +# 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 +# +# REGENDATA ["--travis-patches=travis-patch.patch","sourcehut","travis-patch.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.6.4 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_6_4-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.6.4 + - 8_6_4-check: | + cd example.org + cabal check + - 8_6_4-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_6_4-build: | + cd example.org + cabal build all + - 8_6_4-test: | + cd example.org + cabal test all --enable-tests + - 8_6_4-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.6.5 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--travis-patches=travis-patch.patch' 'sourcehut' 'travis-patch.project' +# +# 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 +# +# REGENDATA ["--travis-patches=travis-patch.patch","sourcehut","travis-patch.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.6.5 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_6_5-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.6.5 + - 8_6_5-check: | + cd example.org + cabal check + - 8_6_5-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_6_5-build: | + cd example.org + cabal build all + - 8_6_5-test: | + cd example.org + cabal test all --enable-tests + - 8_6_5-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.8.1 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--travis-patches=travis-patch.patch' 'sourcehut' 'travis-patch.project' +# +# 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 +# +# REGENDATA ["--travis-patches=travis-patch.patch","sourcehut","travis-patch.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.8.1 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_8_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.8.1 + - 8_8_1-check: | + cd example.org + cabal check + - 8_8_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_8_1-build: | + cd example.org + cabal build all + - 8_8_1-test: | + cd example.org + cabal test all --enable-tests + - 8_8_1-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.8.2 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--travis-patches=travis-patch.patch' 'sourcehut' 'travis-patch.project' +# +# 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 +# +# REGENDATA ["--travis-patches=travis-patch.patch","sourcehut","travis-patch.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.8.2 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_8_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.8.2 + - 8_8_2-check: | + cd example.org + cabal check + - 8_8_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_8_2-build: | + cd example.org + cabal build all + - 8_8_2-test: | + cd example.org + cabal test all --enable-tests + - 8_8_2-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.8.3 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--travis-patches=travis-patch.patch' 'sourcehut' 'travis-patch.project' +# +# 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 +# +# REGENDATA ["--travis-patches=travis-patch.patch","sourcehut","travis-patch.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.8.3 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_8_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.8.3 + - 8_8_3-check: | + cd example.org + cabal check + - 8_8_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_8_3-build: | + cd example.org + cabal build all + - 8_8_3-test: | + cd example.org + cabal test all --enable-tests + - 8_8_3-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.8.4 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--travis-patches=travis-patch.patch' 'sourcehut' 'travis-patch.project' +# +# 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 +# +# REGENDATA ["--travis-patches=travis-patch.patch","sourcehut","travis-patch.project"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.8.4 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_8_4-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.8.4 + - 8_8_4-check: | + cd example.org + cabal check + - 8_8_4-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_8_4-build: | + cd example.org + cabal build all + - 8_8_4-test: | + cd example.org + cabal test all --enable-tests + - 8_8_4-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com diff --git a/haskell-ci.cabal b/haskell-ci.cabal index 327fb307..3f1e6750 100644 --- a/haskell-ci.cabal +++ b/haskell-ci.cabal @@ -199,6 +199,7 @@ test-suite golden , base-compat , bytestring , Cabal + , containers , directory , filepath , haskell-ci-internal diff --git a/src/HaskellCI.hs b/src/HaskellCI.hs index 496cb8c5..5d893e8e 100644 --- a/src/HaskellCI.hs +++ b/src/HaskellCI.hs @@ -24,6 +24,7 @@ module HaskellCI ( bashFromConfigFile, travisFromConfigFile, githubFromConfigFile, + sourcehutFromConfigFile, ) where import HaskellCI.Prelude diff --git a/test/Tests.hs b/test/Tests.hs index 022cd963..976c81a9 100644 --- a/test/Tests.hs +++ b/test/Tests.hs @@ -5,6 +5,7 @@ import Prelude () import Prelude.Compat import HaskellCI hiding (main) +import HaskellCI.Sourcehut (SourcehutOptions(..)) import Control.Arrow (first) import Data.Algorithm.Diff (PolyDiff (..), getGroupedDiff) @@ -18,6 +19,8 @@ import qualified Data.ByteString as BS import qualified Data.ByteString.Char8 as BS8 import qualified System.Console.ANSI as ANSI +import qualified Data.Map as Map + main :: IO () main = do setCurrentDirectory "fixtures/" @@ -44,13 +47,25 @@ main = do -- @ fixtureGoldenTest :: FilePath -> TestTree fixtureGoldenTest fp = testGroup fp - [ fixtureGoldenTest' "travis" travisFromConfigFile - , fixtureGoldenTest' "github" githubFromConfigFile - , fixtureGoldenTest' "bash" bashFromConfigFile + [ fixtureGoldenTest' "travis" "travis" travisFromConfigFile + , fixtureGoldenTest' "github" "github" githubFromConfigFile + , fixtureGoldenTest' "bash" "bash" bashFromConfigFile + , fixtureGoldenTest' "sourcehut" "sourcehut" (sourcehutFromConfigFile' False) + , fixtureGoldenTest' "sourcehut-parallel" "sourcehut" (sourcehutFromConfigFile' True) ] where - -- name acts as extension also - fixtureGoldenTest' name generate = cabalGoldenTest name outputRef $ do + sourcehutFromConfigFile' parallel argv opts projectfp = + BS.concat <$> fmap addSourcehutHeader <$> Map.toList <$> + sourcehutFromConfigFile argv opts SourcehutOptions + { sourcehutOptPath = projectfp + , sourcehutOptSource = Just "https://example.org" + , sourcehutOptParallel = parallel + } + + addSourcehutHeader :: (FilePath, BS.ByteString) -> BS.ByteString + addSourcehutHeader (n, m) = BS8.pack ("# manifest name: " <> n <> "\n") <> m + + fixtureGoldenTest' name command generate = cabalGoldenTest name outputRef $ do (argv, opts') <- makeFlags let opts = opts' { optInputType = Just InputTypeProject @@ -70,7 +85,7 @@ fixtureGoldenTest fp = testGroup fp makeFlags :: IO ([String], Options) makeFlags = do argv <- readArgv - let argv' = argv ++ [name, projectfp] + let argv' = argv ++ [command, projectfp] (_fp, opts) <- parseOptions argv' return (argv', opts) From 96ab4eee4c229edeaef61e3b742a00d6cfb26892 Mon Sep 17 00:00:00 2001 From: Francesco Gazzetta Date: Mon, 29 Nov 2021 20:50:16 +0100 Subject: [PATCH 15/23] sourcehut: move options to Config --- fixtures/all-versions.bash | 2 +- fixtures/all-versions.github | 4 +- fixtures/all-versions.sourcehut | 4 +- fixtures/all-versions.sourcehut-parallel | 2252 ------------------ fixtures/all-versions.travis | 4 +- fixtures/copy-fields-all.bash | 2 +- fixtures/copy-fields-all.github | 4 +- fixtures/copy-fields-all.sourcehut | 4 +- fixtures/copy-fields-all.sourcehut-parallel | 1552 ------------ fixtures/copy-fields-all.travis | 4 +- fixtures/copy-fields-none.bash | 2 +- fixtures/copy-fields-none.github | 4 +- fixtures/copy-fields-none.sourcehut | 4 +- fixtures/copy-fields-none.sourcehut-parallel | 1552 ------------ fixtures/copy-fields-none.travis | 4 +- fixtures/copy-fields-some.bash | 2 +- fixtures/copy-fields-some.github | 4 +- fixtures/copy-fields-some.sourcehut | 4 +- fixtures/copy-fields-some.sourcehut-parallel | 1552 ------------ fixtures/copy-fields-some.travis | 4 +- fixtures/empty-line.bash | 2 +- fixtures/empty-line.github | 4 +- fixtures/empty-line.sourcehut | 4 +- fixtures/empty-line.sourcehut-parallel | 1602 ------------- fixtures/empty-line.travis | 4 +- fixtures/enabled-jobs.bash | 2 +- fixtures/enabled-jobs.github | 4 +- fixtures/enabled-jobs.sourcehut | 4 +- fixtures/enabled-jobs.sourcehut-parallel | 1352 ----------- fixtures/enabled-jobs.travis | 4 +- fixtures/fail-versions.sourcehut-parallel | 3 - fixtures/irc-channels.bash | 2 +- fixtures/irc-channels.github | 4 +- fixtures/irc-channels.sourcehut | 4 +- fixtures/irc-channels.sourcehut-parallel | 1552 ------------ fixtures/irc-channels.travis | 4 +- fixtures/messy.bash | 2 +- fixtures/messy.github | 4 +- fixtures/messy.sourcehut | 4 +- fixtures/messy.sourcehut-parallel | 1634 ------------- fixtures/messy.travis | 4 +- fixtures/psql.bash | 2 +- fixtures/psql.github | 4 +- fixtures/psql.sourcehut | 4 +- fixtures/psql.sourcehut-parallel | 1552 ------------ fixtures/psql.travis | 4 +- fixtures/travis-patch.bash | 2 +- fixtures/travis-patch.github | 4 +- fixtures/travis-patch.sourcehut | 4 +- fixtures/travis-patch.sourcehut-parallel | 1552 ------------ fixtures/travis-patch.travis | 4 +- src/HaskellCI.hs | 45 +- src/HaskellCI/Cli.hs | 33 +- src/HaskellCI/Config.hs | 8 + src/HaskellCI/Sourcehut.hs | 44 +- test/Tests.hs | 27 +- 56 files changed, 139 insertions(+), 16313 deletions(-) delete mode 100644 fixtures/all-versions.sourcehut-parallel delete mode 100644 fixtures/copy-fields-all.sourcehut-parallel delete mode 100644 fixtures/copy-fields-none.sourcehut-parallel delete mode 100644 fixtures/copy-fields-some.sourcehut-parallel delete mode 100644 fixtures/empty-line.sourcehut-parallel delete mode 100644 fixtures/enabled-jobs.sourcehut-parallel delete mode 100644 fixtures/fail-versions.sourcehut-parallel delete mode 100644 fixtures/irc-channels.sourcehut-parallel delete mode 100644 fixtures/messy.sourcehut-parallel delete mode 100644 fixtures/psql.sourcehut-parallel delete mode 100644 fixtures/travis-patch.sourcehut-parallel diff --git a/fixtures/all-versions.bash b/fixtures/all-versions.bash index 60a75527..6e12dfcb 100644 --- a/fixtures/all-versions.bash +++ b/fixtures/all-versions.bash @@ -2,7 +2,7 @@ # *INFO* Generating Bash script for testing for GHC versions: 7.0.1 7.0.2 7.0.3 7.0.4 7.2.1 7.2.2 7.4.1 7.4.2 7.6.1 7.6.2 7.6.3 7.8.1 7.8.2 7.8.3 7.8.4 7.10.1 7.10.2 7.10.3 8.0.1 8.0.2 8.2.1 8.2.2 8.4.1 8.4.2 8.4.3 8.4.4 8.6.1 8.6.2 8.6.3 8.6.4 8.6.5 8.8.1 8.8.2 8.8.3 8.8.4 8.10.1 8.10.2 8.10.3 8.10.4 8.10.5 8.10.6 8.10.7 9.0.1 9.0.2 9.2.1 9.2.2 9.2.3 9.4.1 ghcjs-8.4 #!/bin/bash # shellcheck disable=SC2086,SC2016,SC2046 -# REGENDATA ["bash","all-versions.project"] +# REGENDATA ["bash","all-versions.project","--sourcehut-source","https://example.org"] set -o pipefail diff --git a/fixtures/all-versions.github b/fixtures/all-versions.github index a8f4955f..e50dbe82 100644 --- a/fixtures/all-versions.github +++ b/fixtures/all-versions.github @@ -2,7 +2,7 @@ # *INFO* Generating GitHub config for testing for GHC versions: 7.0.1 7.0.2 7.0.3 7.0.4 7.2.1 7.2.2 7.4.1 7.4.2 7.6.1 7.6.2 7.6.3 7.8.1 7.8.2 7.8.3 7.8.4 7.10.1 7.10.2 7.10.3 8.0.1 8.0.2 8.2.1 8.2.2 8.4.1 8.4.2 8.4.3 8.4.4 8.6.1 8.6.2 8.6.3 8.6.4 8.6.5 8.8.1 8.8.2 8.8.3 8.8.4 8.10.1 8.10.2 8.10.3 8.10.4 8.10.5 8.10.6 8.10.7 9.0.1 9.0.2 9.2.1 9.2.2 9.2.3 9.4.1 ghcjs-8.4 # This GitHub workflow config has been generated by a script via # -# haskell-ci 'github' 'all-versions.project' +# haskell-ci 'github' 'all-versions.project' '--sourcehut-source' 'https://example.org' # # To regenerate the script (for example after adjusting tested-with) run # @@ -10,7 +10,7 @@ # # For more information, see https://github.com/haskell-CI/haskell-ci # -# REGENDATA ["github","all-versions.project"] +# REGENDATA ["github","all-versions.project","--sourcehut-source","https://example.org"] # name: Haskell-CI on: diff --git a/fixtures/all-versions.sourcehut b/fixtures/all-versions.sourcehut index d4095ad2..f843761d 100644 --- a/fixtures/all-versions.sourcehut +++ b/fixtures/all-versions.sourcehut @@ -3,7 +3,7 @@ # manifest name: all # This Sourcehut job script has been generated by a script via # -# haskell-ci 'sourcehut' 'all-versions.project' +# haskell-ci 'sourcehut' 'all-versions.project' '--sourcehut-source' 'https://example.org' # # To regenerate the script (for example after adjusting tested-with) run # @@ -11,7 +11,7 @@ # # For more information, see https://github.com/haskell-CI/haskell-ci # -# REGENDATA ["sourcehut","all-versions.project"] +# REGENDATA ["sourcehut","all-versions.project","--sourcehut-source","https://example.org"] # image: ubuntu/bionic packages: diff --git a/fixtures/all-versions.sourcehut-parallel b/fixtures/all-versions.sourcehut-parallel deleted file mode 100644 index 57690f2a..00000000 --- a/fixtures/all-versions.sourcehut-parallel +++ /dev/null @@ -1,2252 +0,0 @@ -# SUCCESS -# *INFO* Generating Sourcehut config for testing for GHC versions: 7.0.1 7.0.2 7.0.3 7.0.4 7.2.1 7.2.2 7.4.1 7.4.2 7.6.1 7.6.2 7.6.3 7.8.1 7.8.2 7.8.3 7.8.4 7.10.1 7.10.2 7.10.3 8.0.1 8.0.2 8.2.1 8.2.2 8.4.1 8.4.2 8.4.3 8.4.4 8.6.1 8.6.2 8.6.3 8.6.4 8.6.5 8.8.1 8.8.2 8.8.3 8.8.4 8.10.1 8.10.2 8.10.3 8.10.4 8.10.5 8.10.6 8.10.7 9.0.1 9.2.1 ghcjs-8.4 -# manifest name: 7.0.1 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci 'sourcehut' 'all-versions.project' -# -# 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 -# -# REGENDATA ["sourcehut","all-versions.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-7.0.1 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 7_0_1-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.0.1 - - 7_0_1-check: | - cd example.org - cabal check - - 7_0_1-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 7_0_1-build: | - cd example.org - cabal build all - - 7_0_1-test: | - cd example.org - cabal test all --enable-tests - - 7_0_1-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: Oleg Grenrus -# manifest name: 7.0.2 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci 'sourcehut' 'all-versions.project' -# -# 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 -# -# REGENDATA ["sourcehut","all-versions.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-7.0.2 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 7_0_2-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.0.2 - - 7_0_2-check: | - cd example.org - cabal check - - 7_0_2-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 7_0_2-build: | - cd example.org - cabal build all - - 7_0_2-test: | - cd example.org - cabal test all --enable-tests - - 7_0_2-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: Oleg Grenrus -# manifest name: 7.0.3 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci 'sourcehut' 'all-versions.project' -# -# 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 -# -# REGENDATA ["sourcehut","all-versions.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-7.0.3 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 7_0_3-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.0.3 - - 7_0_3-check: | - cd example.org - cabal check - - 7_0_3-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 7_0_3-build: | - cd example.org - cabal build all - - 7_0_3-test: | - cd example.org - cabal test all --enable-tests - - 7_0_3-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: Oleg Grenrus -# manifest name: 7.0.4 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci 'sourcehut' 'all-versions.project' -# -# 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 -# -# REGENDATA ["sourcehut","all-versions.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-7.0.4 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 7_0_4-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.0.4 - - 7_0_4-check: | - cd example.org - cabal check - - 7_0_4-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 7_0_4-build: | - cd example.org - cabal build all - - 7_0_4-test: | - cd example.org - cabal test all --enable-tests - - 7_0_4-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: Oleg Grenrus -# manifest name: 7.10.1 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci 'sourcehut' 'all-versions.project' -# -# 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 -# -# REGENDATA ["sourcehut","all-versions.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-7.10.1 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 7_10_1-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.10.1 - - 7_10_1-check: | - cd example.org - cabal check - - 7_10_1-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 7_10_1-build: | - cd example.org - cabal build all - - 7_10_1-test: | - cd example.org - cabal test all --enable-tests - - 7_10_1-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: Oleg Grenrus -# manifest name: 7.10.2 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci 'sourcehut' 'all-versions.project' -# -# 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 -# -# REGENDATA ["sourcehut","all-versions.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-7.10.2 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 7_10_2-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.10.2 - - 7_10_2-check: | - cd example.org - cabal check - - 7_10_2-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 7_10_2-build: | - cd example.org - cabal build all - - 7_10_2-test: | - cd example.org - cabal test all --enable-tests - - 7_10_2-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: Oleg Grenrus -# manifest name: 7.10.3 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci 'sourcehut' 'all-versions.project' -# -# 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 -# -# REGENDATA ["sourcehut","all-versions.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-7.10.3 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 7_10_3-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.10.3 - - 7_10_3-check: | - cd example.org - cabal check - - 7_10_3-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 7_10_3-build: | - cd example.org - cabal build all - - 7_10_3-test: | - cd example.org - cabal test all --enable-tests - - 7_10_3-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: Oleg Grenrus -# manifest name: 7.2.1 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci 'sourcehut' 'all-versions.project' -# -# 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 -# -# REGENDATA ["sourcehut","all-versions.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-7.2.1 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 7_2_1-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.2.1 - - 7_2_1-check: | - cd example.org - cabal check - - 7_2_1-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 7_2_1-build: | - cd example.org - cabal build all - - 7_2_1-test: | - cd example.org - cabal test all --enable-tests - - 7_2_1-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: Oleg Grenrus -# manifest name: 7.2.2 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci 'sourcehut' 'all-versions.project' -# -# 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 -# -# REGENDATA ["sourcehut","all-versions.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-7.2.2 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 7_2_2-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.2.2 - - 7_2_2-check: | - cd example.org - cabal check - - 7_2_2-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 7_2_2-build: | - cd example.org - cabal build all - - 7_2_2-test: | - cd example.org - cabal test all --enable-tests - - 7_2_2-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: Oleg Grenrus -# manifest name: 7.4.1 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci 'sourcehut' 'all-versions.project' -# -# 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 -# -# REGENDATA ["sourcehut","all-versions.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-7.4.1 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 7_4_1-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.4.1 - - 7_4_1-check: | - cd example.org - cabal check - - 7_4_1-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 7_4_1-build: | - cd example.org - cabal build all - - 7_4_1-test: | - cd example.org - cabal test all --enable-tests - - 7_4_1-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: Oleg Grenrus -# manifest name: 7.4.2 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci 'sourcehut' 'all-versions.project' -# -# 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 -# -# REGENDATA ["sourcehut","all-versions.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-7.4.2 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 7_4_2-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.4.2 - - 7_4_2-check: | - cd example.org - cabal check - - 7_4_2-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 7_4_2-build: | - cd example.org - cabal build all - - 7_4_2-test: | - cd example.org - cabal test all --enable-tests - - 7_4_2-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: Oleg Grenrus -# manifest name: 7.6.1 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci 'sourcehut' 'all-versions.project' -# -# 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 -# -# REGENDATA ["sourcehut","all-versions.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-7.6.1 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 7_6_1-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.6.1 - - 7_6_1-check: | - cd example.org - cabal check - - 7_6_1-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 7_6_1-build: | - cd example.org - cabal build all - - 7_6_1-test: | - cd example.org - cabal test all --enable-tests - - 7_6_1-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: Oleg Grenrus -# manifest name: 7.6.2 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci 'sourcehut' 'all-versions.project' -# -# 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 -# -# REGENDATA ["sourcehut","all-versions.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-7.6.2 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 7_6_2-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.6.2 - - 7_6_2-check: | - cd example.org - cabal check - - 7_6_2-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 7_6_2-build: | - cd example.org - cabal build all - - 7_6_2-test: | - cd example.org - cabal test all --enable-tests - - 7_6_2-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: Oleg Grenrus -# manifest name: 7.6.3 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci 'sourcehut' 'all-versions.project' -# -# 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 -# -# REGENDATA ["sourcehut","all-versions.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-7.6.3 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 7_6_3-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.6.3 - - 7_6_3-check: | - cd example.org - cabal check - - 7_6_3-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 7_6_3-build: | - cd example.org - cabal build all - - 7_6_3-test: | - cd example.org - cabal test all --enable-tests - - 7_6_3-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: Oleg Grenrus -# manifest name: 7.8.1 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci 'sourcehut' 'all-versions.project' -# -# 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 -# -# REGENDATA ["sourcehut","all-versions.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-7.8.1 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 7_8_1-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.8.1 - - 7_8_1-check: | - cd example.org - cabal check - - 7_8_1-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 7_8_1-build: | - cd example.org - cabal build all - - 7_8_1-test: | - cd example.org - cabal test all --enable-tests - - 7_8_1-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: Oleg Grenrus -# manifest name: 7.8.2 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci 'sourcehut' 'all-versions.project' -# -# 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 -# -# REGENDATA ["sourcehut","all-versions.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-7.8.2 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 7_8_2-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.8.2 - - 7_8_2-check: | - cd example.org - cabal check - - 7_8_2-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 7_8_2-build: | - cd example.org - cabal build all - - 7_8_2-test: | - cd example.org - cabal test all --enable-tests - - 7_8_2-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: Oleg Grenrus -# manifest name: 7.8.3 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci 'sourcehut' 'all-versions.project' -# -# 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 -# -# REGENDATA ["sourcehut","all-versions.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-7.8.3 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 7_8_3-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.8.3 - - 7_8_3-check: | - cd example.org - cabal check - - 7_8_3-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 7_8_3-build: | - cd example.org - cabal build all - - 7_8_3-test: | - cd example.org - cabal test all --enable-tests - - 7_8_3-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: Oleg Grenrus -# manifest name: 7.8.4 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci 'sourcehut' 'all-versions.project' -# -# 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 -# -# REGENDATA ["sourcehut","all-versions.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-7.8.4 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 7_8_4-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.8.4 - - 7_8_4-check: | - cd example.org - cabal check - - 7_8_4-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 7_8_4-build: | - cd example.org - cabal build all - - 7_8_4-test: | - cd example.org - cabal test all --enable-tests - - 7_8_4-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: Oleg Grenrus -# manifest name: 8.0.1 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci 'sourcehut' 'all-versions.project' -# -# 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 -# -# REGENDATA ["sourcehut","all-versions.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.0.1 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_0_1-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.0.1 - - 8_0_1-check: | - cd example.org - cabal check - - 8_0_1-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_0_1-build: | - cd example.org - cabal build all - - 8_0_1-test: | - cd example.org - cabal test all --enable-tests - - 8_0_1-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: Oleg Grenrus -# manifest name: 8.0.2 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci 'sourcehut' 'all-versions.project' -# -# 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 -# -# REGENDATA ["sourcehut","all-versions.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.0.2 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_0_2-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.0.2 - - 8_0_2-check: | - cd example.org - cabal check - - 8_0_2-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_0_2-build: | - cd example.org - cabal build all - - 8_0_2-test: | - cd example.org - cabal test all --enable-tests - - 8_0_2-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: Oleg Grenrus -# manifest name: 8.10.1 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci 'sourcehut' 'all-versions.project' -# -# 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 -# -# REGENDATA ["sourcehut","all-versions.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.10.1 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_10_1-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.1 - - 8_10_1-check: | - cd example.org - cabal check - - 8_10_1-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_10_1-build: | - cd example.org - cabal build all - - 8_10_1-test: | - cd example.org - cabal test all --enable-tests - - 8_10_1-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: Oleg Grenrus -# manifest name: 8.10.2 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci 'sourcehut' 'all-versions.project' -# -# 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 -# -# REGENDATA ["sourcehut","all-versions.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.10.2 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_10_2-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.2 - - 8_10_2-check: | - cd example.org - cabal check - - 8_10_2-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_10_2-build: | - cd example.org - cabal build all - - 8_10_2-test: | - cd example.org - cabal test all --enable-tests - - 8_10_2-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: Oleg Grenrus -# manifest name: 8.10.3 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci 'sourcehut' 'all-versions.project' -# -# 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 -# -# REGENDATA ["sourcehut","all-versions.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.10.3 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_10_3-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.3 - - 8_10_3-check: | - cd example.org - cabal check - - 8_10_3-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_10_3-build: | - cd example.org - cabal build all - - 8_10_3-test: | - cd example.org - cabal test all --enable-tests - - 8_10_3-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: Oleg Grenrus -# manifest name: 8.10.4 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci 'sourcehut' 'all-versions.project' -# -# 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 -# -# REGENDATA ["sourcehut","all-versions.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.10.4 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_10_4-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.4 - - 8_10_4-check: | - cd example.org - cabal check - - 8_10_4-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_10_4-build: | - cd example.org - cabal build all - - 8_10_4-test: | - cd example.org - cabal test all --enable-tests - - 8_10_4-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: Oleg Grenrus -# manifest name: 8.10.5 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci 'sourcehut' 'all-versions.project' -# -# 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 -# -# REGENDATA ["sourcehut","all-versions.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.10.5 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_10_5-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.5 - - 8_10_5-check: | - cd example.org - cabal check - - 8_10_5-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_10_5-build: | - cd example.org - cabal build all - - 8_10_5-test: | - cd example.org - cabal test all --enable-tests - - 8_10_5-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: Oleg Grenrus -# manifest name: 8.10.6 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci 'sourcehut' 'all-versions.project' -# -# 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 -# -# REGENDATA ["sourcehut","all-versions.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.10.6 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_10_6-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.6 - - 8_10_6-check: | - cd example.org - cabal check - - 8_10_6-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_10_6-build: | - cd example.org - cabal build all - - 8_10_6-test: | - cd example.org - cabal test all --enable-tests - - 8_10_6-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: Oleg Grenrus -# manifest name: 8.10.7 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci 'sourcehut' 'all-versions.project' -# -# 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 -# -# REGENDATA ["sourcehut","all-versions.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.10.7 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_10_7-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.7 - - 8_10_7-check: | - cd example.org - cabal check - - 8_10_7-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_10_7-build: | - cd example.org - cabal build all - - 8_10_7-test: | - cd example.org - cabal test all --enable-tests - - 8_10_7-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: Oleg Grenrus -# manifest name: 8.2.1 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci 'sourcehut' 'all-versions.project' -# -# 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 -# -# REGENDATA ["sourcehut","all-versions.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.2.1 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_2_1-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.2.1 - - 8_2_1-check: | - cd example.org - cabal check - - 8_2_1-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_2_1-build: | - cd example.org - cabal build all - - 8_2_1-test: | - cd example.org - cabal test all --enable-tests - - 8_2_1-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: Oleg Grenrus -# manifest name: 8.2.2 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci 'sourcehut' 'all-versions.project' -# -# 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 -# -# REGENDATA ["sourcehut","all-versions.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.2.2 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_2_2-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.2.2 - - 8_2_2-check: | - cd example.org - cabal check - - 8_2_2-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_2_2-build: | - cd example.org - cabal build all - - 8_2_2-test: | - cd example.org - cabal test all --enable-tests - - 8_2_2-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: Oleg Grenrus -# manifest name: 8.4.1 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci 'sourcehut' 'all-versions.project' -# -# 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 -# -# REGENDATA ["sourcehut","all-versions.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.4.1 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_4_1-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.4.1 - - 8_4_1-check: | - cd example.org - cabal check - - 8_4_1-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_4_1-build: | - cd example.org - cabal build all - - 8_4_1-test: | - cd example.org - cabal test all --enable-tests - - 8_4_1-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: Oleg Grenrus -# manifest name: 8.4.2 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci 'sourcehut' 'all-versions.project' -# -# 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 -# -# REGENDATA ["sourcehut","all-versions.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.4.2 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_4_2-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.4.2 - - 8_4_2-check: | - cd example.org - cabal check - - 8_4_2-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_4_2-build: | - cd example.org - cabal build all - - 8_4_2-test: | - cd example.org - cabal test all --enable-tests - - 8_4_2-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: Oleg Grenrus -# manifest name: 8.4.3 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci 'sourcehut' 'all-versions.project' -# -# 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 -# -# REGENDATA ["sourcehut","all-versions.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.4.3 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_4_3-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.4.3 - - 8_4_3-check: | - cd example.org - cabal check - - 8_4_3-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_4_3-build: | - cd example.org - cabal build all - - 8_4_3-test: | - cd example.org - cabal test all --enable-tests - - 8_4_3-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: Oleg Grenrus -# manifest name: 8.4.4 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci 'sourcehut' 'all-versions.project' -# -# 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 -# -# REGENDATA ["sourcehut","all-versions.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.4.4 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_4_4-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.4.4 - - 8_4_4-check: | - cd example.org - cabal check - - 8_4_4-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_4_4-build: | - cd example.org - cabal build all - - 8_4_4-test: | - cd example.org - cabal test all --enable-tests - - 8_4_4-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: Oleg Grenrus -# manifest name: 8.6.1 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci 'sourcehut' 'all-versions.project' -# -# 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 -# -# REGENDATA ["sourcehut","all-versions.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.6.1 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_6_1-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.6.1 - - 8_6_1-check: | - cd example.org - cabal check - - 8_6_1-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_6_1-build: | - cd example.org - cabal build all - - 8_6_1-test: | - cd example.org - cabal test all --enable-tests - - 8_6_1-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: Oleg Grenrus -# manifest name: 8.6.2 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci 'sourcehut' 'all-versions.project' -# -# 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 -# -# REGENDATA ["sourcehut","all-versions.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.6.2 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_6_2-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.6.2 - - 8_6_2-check: | - cd example.org - cabal check - - 8_6_2-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_6_2-build: | - cd example.org - cabal build all - - 8_6_2-test: | - cd example.org - cabal test all --enable-tests - - 8_6_2-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: Oleg Grenrus -# manifest name: 8.6.3 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci 'sourcehut' 'all-versions.project' -# -# 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 -# -# REGENDATA ["sourcehut","all-versions.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.6.3 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_6_3-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.6.3 - - 8_6_3-check: | - cd example.org - cabal check - - 8_6_3-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_6_3-build: | - cd example.org - cabal build all - - 8_6_3-test: | - cd example.org - cabal test all --enable-tests - - 8_6_3-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: Oleg Grenrus -# manifest name: 8.6.4 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci 'sourcehut' 'all-versions.project' -# -# 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 -# -# REGENDATA ["sourcehut","all-versions.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.6.4 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_6_4-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.6.4 - - 8_6_4-check: | - cd example.org - cabal check - - 8_6_4-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_6_4-build: | - cd example.org - cabal build all - - 8_6_4-test: | - cd example.org - cabal test all --enable-tests - - 8_6_4-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: Oleg Grenrus -# manifest name: 8.6.5 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci 'sourcehut' 'all-versions.project' -# -# 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 -# -# REGENDATA ["sourcehut","all-versions.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.6.5 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_6_5-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.6.5 - - 8_6_5-check: | - cd example.org - cabal check - - 8_6_5-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_6_5-build: | - cd example.org - cabal build all - - 8_6_5-test: | - cd example.org - cabal test all --enable-tests - - 8_6_5-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: Oleg Grenrus -# manifest name: 8.8.1 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci 'sourcehut' 'all-versions.project' -# -# 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 -# -# REGENDATA ["sourcehut","all-versions.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.8.1 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_8_1-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.8.1 - - 8_8_1-check: | - cd example.org - cabal check - - 8_8_1-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_8_1-build: | - cd example.org - cabal build all - - 8_8_1-test: | - cd example.org - cabal test all --enable-tests - - 8_8_1-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: Oleg Grenrus -# manifest name: 8.8.2 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci 'sourcehut' 'all-versions.project' -# -# 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 -# -# REGENDATA ["sourcehut","all-versions.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.8.2 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_8_2-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.8.2 - - 8_8_2-check: | - cd example.org - cabal check - - 8_8_2-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_8_2-build: | - cd example.org - cabal build all - - 8_8_2-test: | - cd example.org - cabal test all --enable-tests - - 8_8_2-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: Oleg Grenrus -# manifest name: 8.8.3 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci 'sourcehut' 'all-versions.project' -# -# 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 -# -# REGENDATA ["sourcehut","all-versions.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.8.3 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_8_3-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.8.3 - - 8_8_3-check: | - cd example.org - cabal check - - 8_8_3-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_8_3-build: | - cd example.org - cabal build all - - 8_8_3-test: | - cd example.org - cabal test all --enable-tests - - 8_8_3-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: Oleg Grenrus -# manifest name: 8.8.4 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci 'sourcehut' 'all-versions.project' -# -# 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 -# -# REGENDATA ["sourcehut","all-versions.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.8.4 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_8_4-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.8.4 - - 8_8_4-check: | - cd example.org - cabal check - - 8_8_4-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_8_4-build: | - cd example.org - cabal build all - - 8_8_4-test: | - cd example.org - cabal test all --enable-tests - - 8_8_4-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: Oleg Grenrus -# manifest name: 9.0.1 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci 'sourcehut' 'all-versions.project' -# -# 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 -# -# REGENDATA ["sourcehut","all-versions.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-9.0.1 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 9_0_1-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-9.0.1 - - 9_0_1-check: | - cd example.org - cabal check - - 9_0_1-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 9_0_1-build: | - cd example.org - cabal build all - - 9_0_1-test: | - cd example.org - cabal test all --enable-tests - - 9_0_1-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: Oleg Grenrus -# manifest name: 9.2.1 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci 'sourcehut' 'all-versions.project' -# -# 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 -# -# REGENDATA ["sourcehut","all-versions.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-9.2.1 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 9_2_1-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-9.2.1 - - 9_2_1-check: | - cd example.org - cabal check - - 9_2_1-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 9_2_1-build: | - cd example.org - cabal build all - - 9_2_1-test: | - cd example.org - cabal test all --enable-tests - - 9_2_1-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: Oleg Grenrus -# manifest name: ghcjs-8.4 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci 'sourcehut' 'all-versions.project' -# -# 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 -# -# REGENDATA ["sourcehut","all-versions.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghcjs-8.4 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - ghcjs-8_4-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghcjs-8.4 - - ghcjs-8_4-check: | - cd example.org - cabal check - - ghcjs-8_4-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - ghcjs-8_4-build: | - cd example.org - cabal build all - - ghcjs-8_4-test: | - cd example.org - cabal test all --enable-tests - - ghcjs-8_4-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: Oleg Grenrus diff --git a/fixtures/all-versions.travis b/fixtures/all-versions.travis index 144ee587..29495a80 100644 --- a/fixtures/all-versions.travis +++ b/fixtures/all-versions.travis @@ -2,7 +2,7 @@ # *INFO* Generating Travis-CI config for testing for GHC versions: 7.0.1 7.0.2 7.0.3 7.0.4 7.2.1 7.2.2 7.4.1 7.4.2 7.6.1 7.6.2 7.6.3 7.8.1 7.8.2 7.8.3 7.8.4 7.10.1 7.10.2 7.10.3 8.0.1 8.0.2 8.2.1 8.2.2 8.4.1 8.4.2 8.4.3 8.4.4 8.6.1 8.6.2 8.6.3 8.6.4 8.6.5 8.8.1 8.8.2 8.8.3 8.8.4 8.10.1 8.10.2 8.10.3 8.10.4 8.10.5 8.10.6 8.10.7 9.0.1 9.0.2 9.2.1 9.2.2 9.2.3 9.4.1 ghcjs-8.4 # This Travis job script has been generated by a script via # -# haskell-ci 'travis' 'all-versions.project' +# haskell-ci 'travis' 'all-versions.project' '--sourcehut-source' 'https://example.org' # # To regenerate the script (for example after adjusting tested-with) run # @@ -310,5 +310,5 @@ script: - rm -f cabal.project.local - ${CABAL} v2-build $WITHCOMPILER --disable-tests --disable-benchmarks all -# REGENDATA ["travis","all-versions.project"] +# REGENDATA ["travis","all-versions.project","--sourcehut-source","https://example.org"] # EOF diff --git a/fixtures/copy-fields-all.bash b/fixtures/copy-fields-all.bash index d5dbc605..954a16b2 100644 --- a/fixtures/copy-fields-all.bash +++ b/fixtures/copy-fields-all.bash @@ -2,7 +2,7 @@ # *INFO* Generating Bash script for testing for GHC versions: 7.8.1 7.8.2 7.8.3 7.8.4 7.10.1 7.10.2 7.10.3 8.0.1 8.0.2 8.2.1 8.2.2 8.4.1 8.4.2 8.4.3 8.4.4 8.6.1 8.6.2 8.6.3 8.6.4 8.6.5 8.8.1 8.8.2 8.8.3 8.8.4 8.10.1 8.10.2 8.10.3 8.10.4 8.10.5 8.10.6 8.10.7 #!/bin/bash # shellcheck disable=SC2086,SC2016,SC2046 -# REGENDATA ["--copy-fields=all","bash","copy-fields-all.project"] +# REGENDATA ["--copy-fields=all","bash","copy-fields-all.project","--sourcehut-source","https://example.org"] set -o pipefail diff --git a/fixtures/copy-fields-all.github b/fixtures/copy-fields-all.github index 0aa7fc5d..fe9706e6 100644 --- a/fixtures/copy-fields-all.github +++ b/fixtures/copy-fields-all.github @@ -2,7 +2,7 @@ # *INFO* Generating GitHub config for testing for GHC versions: 7.8.1 7.8.2 7.8.3 7.8.4 7.10.1 7.10.2 7.10.3 8.0.1 8.0.2 8.2.1 8.2.2 8.4.1 8.4.2 8.4.3 8.4.4 8.6.1 8.6.2 8.6.3 8.6.4 8.6.5 8.8.1 8.8.2 8.8.3 8.8.4 8.10.1 8.10.2 8.10.3 8.10.4 8.10.5 8.10.6 8.10.7 # This GitHub workflow config has been generated by a script via # -# haskell-ci '--copy-fields=all' 'github' 'copy-fields-all.project' +# haskell-ci '--copy-fields=all' 'github' 'copy-fields-all.project' '--sourcehut-source' 'https://example.org' # # To regenerate the script (for example after adjusting tested-with) run # @@ -10,7 +10,7 @@ # # For more information, see https://github.com/haskell-CI/haskell-ci # -# REGENDATA ["--copy-fields=all","github","copy-fields-all.project"] +# REGENDATA ["--copy-fields=all","github","copy-fields-all.project","--sourcehut-source","https://example.org"] # name: Haskell-CI on: diff --git a/fixtures/copy-fields-all.sourcehut b/fixtures/copy-fields-all.sourcehut index 8f18703c..aaa0198c 100644 --- a/fixtures/copy-fields-all.sourcehut +++ b/fixtures/copy-fields-all.sourcehut @@ -3,7 +3,7 @@ # manifest name: all # This Sourcehut job script has been generated by a script via # -# haskell-ci '--copy-fields=all' 'sourcehut' 'copy-fields-all.project' +# haskell-ci '--copy-fields=all' 'sourcehut' 'copy-fields-all.project' '--sourcehut-source' 'https://example.org' # # To regenerate the script (for example after adjusting tested-with) run # @@ -11,7 +11,7 @@ # # For more information, see https://github.com/haskell-CI/haskell-ci # -# REGENDATA ["--copy-fields=all","sourcehut","copy-fields-all.project"] +# REGENDATA ["--copy-fields=all","sourcehut","copy-fields-all.project","--sourcehut-source","https://example.org"] # image: ubuntu/bionic packages: diff --git a/fixtures/copy-fields-all.sourcehut-parallel b/fixtures/copy-fields-all.sourcehut-parallel deleted file mode 100644 index 246363b0..00000000 --- a/fixtures/copy-fields-all.sourcehut-parallel +++ /dev/null @@ -1,1552 +0,0 @@ -# SUCCESS -# *INFO* Generating Sourcehut config for testing for GHC versions: 7.8.1 7.8.2 7.8.3 7.8.4 7.10.1 7.10.2 7.10.3 8.0.1 8.0.2 8.2.1 8.2.2 8.4.1 8.4.2 8.4.3 8.4.4 8.6.1 8.6.2 8.6.3 8.6.4 8.6.5 8.8.1 8.8.2 8.8.3 8.8.4 8.10.1 8.10.2 8.10.3 8.10.4 8.10.5 8.10.6 8.10.7 -# manifest name: 7.10.1 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--copy-fields=all' 'sourcehut' 'copy-fields-all.project' -# -# 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 -# -# REGENDATA ["--copy-fields=all","sourcehut","copy-fields-all.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-7.10.1 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 7_10_1-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.10.1 - - 7_10_1-check: | - cd example.org - cabal check - - 7_10_1-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 7_10_1-build: | - cd example.org - cabal build all - - 7_10_1-test: | - cd example.org - cabal test all --enable-tests - - 7_10_1-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 7.10.2 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--copy-fields=all' 'sourcehut' 'copy-fields-all.project' -# -# 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 -# -# REGENDATA ["--copy-fields=all","sourcehut","copy-fields-all.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-7.10.2 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 7_10_2-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.10.2 - - 7_10_2-check: | - cd example.org - cabal check - - 7_10_2-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 7_10_2-build: | - cd example.org - cabal build all - - 7_10_2-test: | - cd example.org - cabal test all --enable-tests - - 7_10_2-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 7.10.3 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--copy-fields=all' 'sourcehut' 'copy-fields-all.project' -# -# 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 -# -# REGENDATA ["--copy-fields=all","sourcehut","copy-fields-all.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-7.10.3 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 7_10_3-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.10.3 - - 7_10_3-check: | - cd example.org - cabal check - - 7_10_3-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 7_10_3-build: | - cd example.org - cabal build all - - 7_10_3-test: | - cd example.org - cabal test all --enable-tests - - 7_10_3-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 7.8.1 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--copy-fields=all' 'sourcehut' 'copy-fields-all.project' -# -# 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 -# -# REGENDATA ["--copy-fields=all","sourcehut","copy-fields-all.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-7.8.1 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 7_8_1-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.8.1 - - 7_8_1-check: | - cd example.org - cabal check - - 7_8_1-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 7_8_1-build: | - cd example.org - cabal build all - - 7_8_1-test: | - cd example.org - cabal test all --enable-tests - - 7_8_1-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 7.8.2 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--copy-fields=all' 'sourcehut' 'copy-fields-all.project' -# -# 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 -# -# REGENDATA ["--copy-fields=all","sourcehut","copy-fields-all.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-7.8.2 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 7_8_2-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.8.2 - - 7_8_2-check: | - cd example.org - cabal check - - 7_8_2-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 7_8_2-build: | - cd example.org - cabal build all - - 7_8_2-test: | - cd example.org - cabal test all --enable-tests - - 7_8_2-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 7.8.3 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--copy-fields=all' 'sourcehut' 'copy-fields-all.project' -# -# 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 -# -# REGENDATA ["--copy-fields=all","sourcehut","copy-fields-all.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-7.8.3 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 7_8_3-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.8.3 - - 7_8_3-check: | - cd example.org - cabal check - - 7_8_3-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 7_8_3-build: | - cd example.org - cabal build all - - 7_8_3-test: | - cd example.org - cabal test all --enable-tests - - 7_8_3-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 7.8.4 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--copy-fields=all' 'sourcehut' 'copy-fields-all.project' -# -# 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 -# -# REGENDATA ["--copy-fields=all","sourcehut","copy-fields-all.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-7.8.4 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 7_8_4-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.8.4 - - 7_8_4-check: | - cd example.org - cabal check - - 7_8_4-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 7_8_4-build: | - cd example.org - cabal build all - - 7_8_4-test: | - cd example.org - cabal test all --enable-tests - - 7_8_4-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.0.1 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--copy-fields=all' 'sourcehut' 'copy-fields-all.project' -# -# 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 -# -# REGENDATA ["--copy-fields=all","sourcehut","copy-fields-all.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.0.1 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_0_1-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.0.1 - - 8_0_1-check: | - cd example.org - cabal check - - 8_0_1-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_0_1-build: | - cd example.org - cabal build all - - 8_0_1-test: | - cd example.org - cabal test all --enable-tests - - 8_0_1-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.0.2 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--copy-fields=all' 'sourcehut' 'copy-fields-all.project' -# -# 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 -# -# REGENDATA ["--copy-fields=all","sourcehut","copy-fields-all.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.0.2 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_0_2-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.0.2 - - 8_0_2-check: | - cd example.org - cabal check - - 8_0_2-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_0_2-build: | - cd example.org - cabal build all - - 8_0_2-test: | - cd example.org - cabal test all --enable-tests - - 8_0_2-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.10.1 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--copy-fields=all' 'sourcehut' 'copy-fields-all.project' -# -# 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 -# -# REGENDATA ["--copy-fields=all","sourcehut","copy-fields-all.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.10.1 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_10_1-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.1 - - 8_10_1-check: | - cd example.org - cabal check - - 8_10_1-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_10_1-build: | - cd example.org - cabal build all - - 8_10_1-test: | - cd example.org - cabal test all --enable-tests - - 8_10_1-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.10.2 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--copy-fields=all' 'sourcehut' 'copy-fields-all.project' -# -# 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 -# -# REGENDATA ["--copy-fields=all","sourcehut","copy-fields-all.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.10.2 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_10_2-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.2 - - 8_10_2-check: | - cd example.org - cabal check - - 8_10_2-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_10_2-build: | - cd example.org - cabal build all - - 8_10_2-test: | - cd example.org - cabal test all --enable-tests - - 8_10_2-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.10.3 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--copy-fields=all' 'sourcehut' 'copy-fields-all.project' -# -# 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 -# -# REGENDATA ["--copy-fields=all","sourcehut","copy-fields-all.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.10.3 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_10_3-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.3 - - 8_10_3-check: | - cd example.org - cabal check - - 8_10_3-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_10_3-build: | - cd example.org - cabal build all - - 8_10_3-test: | - cd example.org - cabal test all --enable-tests - - 8_10_3-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.10.4 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--copy-fields=all' 'sourcehut' 'copy-fields-all.project' -# -# 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 -# -# REGENDATA ["--copy-fields=all","sourcehut","copy-fields-all.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.10.4 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_10_4-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.4 - - 8_10_4-check: | - cd example.org - cabal check - - 8_10_4-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_10_4-build: | - cd example.org - cabal build all - - 8_10_4-test: | - cd example.org - cabal test all --enable-tests - - 8_10_4-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.10.5 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--copy-fields=all' 'sourcehut' 'copy-fields-all.project' -# -# 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 -# -# REGENDATA ["--copy-fields=all","sourcehut","copy-fields-all.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.10.5 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_10_5-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.5 - - 8_10_5-check: | - cd example.org - cabal check - - 8_10_5-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_10_5-build: | - cd example.org - cabal build all - - 8_10_5-test: | - cd example.org - cabal test all --enable-tests - - 8_10_5-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.10.6 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--copy-fields=all' 'sourcehut' 'copy-fields-all.project' -# -# 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 -# -# REGENDATA ["--copy-fields=all","sourcehut","copy-fields-all.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.10.6 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_10_6-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.6 - - 8_10_6-check: | - cd example.org - cabal check - - 8_10_6-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_10_6-build: | - cd example.org - cabal build all - - 8_10_6-test: | - cd example.org - cabal test all --enable-tests - - 8_10_6-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.10.7 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--copy-fields=all' 'sourcehut' 'copy-fields-all.project' -# -# 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 -# -# REGENDATA ["--copy-fields=all","sourcehut","copy-fields-all.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.10.7 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_10_7-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.7 - - 8_10_7-check: | - cd example.org - cabal check - - 8_10_7-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_10_7-build: | - cd example.org - cabal build all - - 8_10_7-test: | - cd example.org - cabal test all --enable-tests - - 8_10_7-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.2.1 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--copy-fields=all' 'sourcehut' 'copy-fields-all.project' -# -# 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 -# -# REGENDATA ["--copy-fields=all","sourcehut","copy-fields-all.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.2.1 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_2_1-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.2.1 - - 8_2_1-check: | - cd example.org - cabal check - - 8_2_1-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_2_1-build: | - cd example.org - cabal build all - - 8_2_1-test: | - cd example.org - cabal test all --enable-tests - - 8_2_1-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.2.2 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--copy-fields=all' 'sourcehut' 'copy-fields-all.project' -# -# 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 -# -# REGENDATA ["--copy-fields=all","sourcehut","copy-fields-all.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.2.2 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_2_2-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.2.2 - - 8_2_2-check: | - cd example.org - cabal check - - 8_2_2-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_2_2-build: | - cd example.org - cabal build all - - 8_2_2-test: | - cd example.org - cabal test all --enable-tests - - 8_2_2-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.4.1 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--copy-fields=all' 'sourcehut' 'copy-fields-all.project' -# -# 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 -# -# REGENDATA ["--copy-fields=all","sourcehut","copy-fields-all.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.4.1 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_4_1-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.4.1 - - 8_4_1-check: | - cd example.org - cabal check - - 8_4_1-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_4_1-build: | - cd example.org - cabal build all - - 8_4_1-test: | - cd example.org - cabal test all --enable-tests - - 8_4_1-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.4.2 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--copy-fields=all' 'sourcehut' 'copy-fields-all.project' -# -# 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 -# -# REGENDATA ["--copy-fields=all","sourcehut","copy-fields-all.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.4.2 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_4_2-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.4.2 - - 8_4_2-check: | - cd example.org - cabal check - - 8_4_2-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_4_2-build: | - cd example.org - cabal build all - - 8_4_2-test: | - cd example.org - cabal test all --enable-tests - - 8_4_2-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.4.3 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--copy-fields=all' 'sourcehut' 'copy-fields-all.project' -# -# 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 -# -# REGENDATA ["--copy-fields=all","sourcehut","copy-fields-all.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.4.3 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_4_3-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.4.3 - - 8_4_3-check: | - cd example.org - cabal check - - 8_4_3-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_4_3-build: | - cd example.org - cabal build all - - 8_4_3-test: | - cd example.org - cabal test all --enable-tests - - 8_4_3-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.4.4 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--copy-fields=all' 'sourcehut' 'copy-fields-all.project' -# -# 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 -# -# REGENDATA ["--copy-fields=all","sourcehut","copy-fields-all.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.4.4 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_4_4-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.4.4 - - 8_4_4-check: | - cd example.org - cabal check - - 8_4_4-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_4_4-build: | - cd example.org - cabal build all - - 8_4_4-test: | - cd example.org - cabal test all --enable-tests - - 8_4_4-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.6.1 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--copy-fields=all' 'sourcehut' 'copy-fields-all.project' -# -# 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 -# -# REGENDATA ["--copy-fields=all","sourcehut","copy-fields-all.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.6.1 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_6_1-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.6.1 - - 8_6_1-check: | - cd example.org - cabal check - - 8_6_1-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_6_1-build: | - cd example.org - cabal build all - - 8_6_1-test: | - cd example.org - cabal test all --enable-tests - - 8_6_1-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.6.2 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--copy-fields=all' 'sourcehut' 'copy-fields-all.project' -# -# 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 -# -# REGENDATA ["--copy-fields=all","sourcehut","copy-fields-all.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.6.2 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_6_2-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.6.2 - - 8_6_2-check: | - cd example.org - cabal check - - 8_6_2-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_6_2-build: | - cd example.org - cabal build all - - 8_6_2-test: | - cd example.org - cabal test all --enable-tests - - 8_6_2-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.6.3 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--copy-fields=all' 'sourcehut' 'copy-fields-all.project' -# -# 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 -# -# REGENDATA ["--copy-fields=all","sourcehut","copy-fields-all.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.6.3 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_6_3-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.6.3 - - 8_6_3-check: | - cd example.org - cabal check - - 8_6_3-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_6_3-build: | - cd example.org - cabal build all - - 8_6_3-test: | - cd example.org - cabal test all --enable-tests - - 8_6_3-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.6.4 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--copy-fields=all' 'sourcehut' 'copy-fields-all.project' -# -# 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 -# -# REGENDATA ["--copy-fields=all","sourcehut","copy-fields-all.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.6.4 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_6_4-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.6.4 - - 8_6_4-check: | - cd example.org - cabal check - - 8_6_4-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_6_4-build: | - cd example.org - cabal build all - - 8_6_4-test: | - cd example.org - cabal test all --enable-tests - - 8_6_4-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.6.5 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--copy-fields=all' 'sourcehut' 'copy-fields-all.project' -# -# 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 -# -# REGENDATA ["--copy-fields=all","sourcehut","copy-fields-all.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.6.5 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_6_5-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.6.5 - - 8_6_5-check: | - cd example.org - cabal check - - 8_6_5-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_6_5-build: | - cd example.org - cabal build all - - 8_6_5-test: | - cd example.org - cabal test all --enable-tests - - 8_6_5-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.8.1 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--copy-fields=all' 'sourcehut' 'copy-fields-all.project' -# -# 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 -# -# REGENDATA ["--copy-fields=all","sourcehut","copy-fields-all.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.8.1 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_8_1-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.8.1 - - 8_8_1-check: | - cd example.org - cabal check - - 8_8_1-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_8_1-build: | - cd example.org - cabal build all - - 8_8_1-test: | - cd example.org - cabal test all --enable-tests - - 8_8_1-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.8.2 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--copy-fields=all' 'sourcehut' 'copy-fields-all.project' -# -# 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 -# -# REGENDATA ["--copy-fields=all","sourcehut","copy-fields-all.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.8.2 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_8_2-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.8.2 - - 8_8_2-check: | - cd example.org - cabal check - - 8_8_2-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_8_2-build: | - cd example.org - cabal build all - - 8_8_2-test: | - cd example.org - cabal test all --enable-tests - - 8_8_2-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.8.3 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--copy-fields=all' 'sourcehut' 'copy-fields-all.project' -# -# 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 -# -# REGENDATA ["--copy-fields=all","sourcehut","copy-fields-all.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.8.3 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_8_3-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.8.3 - - 8_8_3-check: | - cd example.org - cabal check - - 8_8_3-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_8_3-build: | - cd example.org - cabal build all - - 8_8_3-test: | - cd example.org - cabal test all --enable-tests - - 8_8_3-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.8.4 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--copy-fields=all' 'sourcehut' 'copy-fields-all.project' -# -# 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 -# -# REGENDATA ["--copy-fields=all","sourcehut","copy-fields-all.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.8.4 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_8_4-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.8.4 - - 8_8_4-check: | - cd example.org - cabal check - - 8_8_4-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_8_4-build: | - cd example.org - cabal build all - - 8_8_4-test: | - cd example.org - cabal test all --enable-tests - - 8_8_4-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com diff --git a/fixtures/copy-fields-all.travis b/fixtures/copy-fields-all.travis index be09d4e1..715a38bb 100644 --- a/fixtures/copy-fields-all.travis +++ b/fixtures/copy-fields-all.travis @@ -2,7 +2,7 @@ # *INFO* Generating Travis-CI config for testing for GHC versions: 7.8.1 7.8.2 7.8.3 7.8.4 7.10.1 7.10.2 7.10.3 8.0.1 8.0.2 8.2.1 8.2.2 8.4.1 8.4.2 8.4.3 8.4.4 8.6.1 8.6.2 8.6.3 8.6.4 8.6.5 8.8.1 8.8.2 8.8.3 8.8.4 8.10.1 8.10.2 8.10.3 8.10.4 8.10.5 8.10.6 8.10.7 # This Travis job script has been generated by a script via # -# haskell-ci '--copy-fields=all' 'travis' 'copy-fields-all.project' +# haskell-ci '--copy-fields=all' 'travis' 'copy-fields-all.project' '--sourcehut-source' 'https://example.org' # # To regenerate the script (for example after adjusting tested-with) run # @@ -272,5 +272,5 @@ script: - rm -f cabal.project.local - ${CABAL} v2-build $WITHCOMPILER --disable-tests --disable-benchmarks all -# REGENDATA ["--copy-fields=all","travis","copy-fields-all.project"] +# REGENDATA ["--copy-fields=all","travis","copy-fields-all.project","--sourcehut-source","https://example.org"] # EOF diff --git a/fixtures/copy-fields-none.bash b/fixtures/copy-fields-none.bash index edf57075..bdebf4db 100644 --- a/fixtures/copy-fields-none.bash +++ b/fixtures/copy-fields-none.bash @@ -2,7 +2,7 @@ # *INFO* Generating Bash script for testing for GHC versions: 7.8.1 7.8.2 7.8.3 7.8.4 7.10.1 7.10.2 7.10.3 8.0.1 8.0.2 8.2.1 8.2.2 8.4.1 8.4.2 8.4.3 8.4.4 8.6.1 8.6.2 8.6.3 8.6.4 8.6.5 8.8.1 8.8.2 8.8.3 8.8.4 8.10.1 8.10.2 8.10.3 8.10.4 8.10.5 8.10.6 8.10.7 #!/bin/bash # shellcheck disable=SC2086,SC2016,SC2046 -# REGENDATA ["--copy-fields=none","bash","copy-fields-none.project"] +# REGENDATA ["--copy-fields=none","bash","copy-fields-none.project","--sourcehut-source","https://example.org"] set -o pipefail diff --git a/fixtures/copy-fields-none.github b/fixtures/copy-fields-none.github index 6119f240..a853a291 100644 --- a/fixtures/copy-fields-none.github +++ b/fixtures/copy-fields-none.github @@ -2,7 +2,7 @@ # *INFO* Generating GitHub config for testing for GHC versions: 7.8.1 7.8.2 7.8.3 7.8.4 7.10.1 7.10.2 7.10.3 8.0.1 8.0.2 8.2.1 8.2.2 8.4.1 8.4.2 8.4.3 8.4.4 8.6.1 8.6.2 8.6.3 8.6.4 8.6.5 8.8.1 8.8.2 8.8.3 8.8.4 8.10.1 8.10.2 8.10.3 8.10.4 8.10.5 8.10.6 8.10.7 # This GitHub workflow config has been generated by a script via # -# haskell-ci '--copy-fields=none' 'github' 'copy-fields-none.project' +# haskell-ci '--copy-fields=none' 'github' 'copy-fields-none.project' '--sourcehut-source' 'https://example.org' # # To regenerate the script (for example after adjusting tested-with) run # @@ -10,7 +10,7 @@ # # For more information, see https://github.com/haskell-CI/haskell-ci # -# REGENDATA ["--copy-fields=none","github","copy-fields-none.project"] +# REGENDATA ["--copy-fields=none","github","copy-fields-none.project","--sourcehut-source","https://example.org"] # name: Haskell-CI on: diff --git a/fixtures/copy-fields-none.sourcehut b/fixtures/copy-fields-none.sourcehut index fa06c322..eb3356c9 100644 --- a/fixtures/copy-fields-none.sourcehut +++ b/fixtures/copy-fields-none.sourcehut @@ -3,7 +3,7 @@ # manifest name: all # This Sourcehut job script has been generated by a script via # -# haskell-ci '--copy-fields=none' 'sourcehut' 'copy-fields-none.project' +# haskell-ci '--copy-fields=none' 'sourcehut' 'copy-fields-none.project' '--sourcehut-source' 'https://example.org' # # To regenerate the script (for example after adjusting tested-with) run # @@ -11,7 +11,7 @@ # # For more information, see https://github.com/haskell-CI/haskell-ci # -# REGENDATA ["--copy-fields=none","sourcehut","copy-fields-none.project"] +# REGENDATA ["--copy-fields=none","sourcehut","copy-fields-none.project","--sourcehut-source","https://example.org"] # image: ubuntu/bionic packages: diff --git a/fixtures/copy-fields-none.sourcehut-parallel b/fixtures/copy-fields-none.sourcehut-parallel deleted file mode 100644 index 5cfc358c..00000000 --- a/fixtures/copy-fields-none.sourcehut-parallel +++ /dev/null @@ -1,1552 +0,0 @@ -# SUCCESS -# *INFO* Generating Sourcehut config for testing for GHC versions: 7.8.1 7.8.2 7.8.3 7.8.4 7.10.1 7.10.2 7.10.3 8.0.1 8.0.2 8.2.1 8.2.2 8.4.1 8.4.2 8.4.3 8.4.4 8.6.1 8.6.2 8.6.3 8.6.4 8.6.5 8.8.1 8.8.2 8.8.3 8.8.4 8.10.1 8.10.2 8.10.3 8.10.4 8.10.5 8.10.6 8.10.7 -# manifest name: 7.10.1 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--copy-fields=none' 'sourcehut' 'copy-fields-none.project' -# -# 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 -# -# REGENDATA ["--copy-fields=none","sourcehut","copy-fields-none.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-7.10.1 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 7_10_1-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.10.1 - - 7_10_1-check: | - cd example.org - cabal check - - 7_10_1-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 7_10_1-build: | - cd example.org - cabal build all - - 7_10_1-test: | - cd example.org - cabal test all --enable-tests - - 7_10_1-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 7.10.2 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--copy-fields=none' 'sourcehut' 'copy-fields-none.project' -# -# 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 -# -# REGENDATA ["--copy-fields=none","sourcehut","copy-fields-none.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-7.10.2 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 7_10_2-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.10.2 - - 7_10_2-check: | - cd example.org - cabal check - - 7_10_2-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 7_10_2-build: | - cd example.org - cabal build all - - 7_10_2-test: | - cd example.org - cabal test all --enable-tests - - 7_10_2-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 7.10.3 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--copy-fields=none' 'sourcehut' 'copy-fields-none.project' -# -# 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 -# -# REGENDATA ["--copy-fields=none","sourcehut","copy-fields-none.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-7.10.3 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 7_10_3-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.10.3 - - 7_10_3-check: | - cd example.org - cabal check - - 7_10_3-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 7_10_3-build: | - cd example.org - cabal build all - - 7_10_3-test: | - cd example.org - cabal test all --enable-tests - - 7_10_3-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 7.8.1 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--copy-fields=none' 'sourcehut' 'copy-fields-none.project' -# -# 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 -# -# REGENDATA ["--copy-fields=none","sourcehut","copy-fields-none.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-7.8.1 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 7_8_1-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.8.1 - - 7_8_1-check: | - cd example.org - cabal check - - 7_8_1-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 7_8_1-build: | - cd example.org - cabal build all - - 7_8_1-test: | - cd example.org - cabal test all --enable-tests - - 7_8_1-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 7.8.2 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--copy-fields=none' 'sourcehut' 'copy-fields-none.project' -# -# 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 -# -# REGENDATA ["--copy-fields=none","sourcehut","copy-fields-none.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-7.8.2 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 7_8_2-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.8.2 - - 7_8_2-check: | - cd example.org - cabal check - - 7_8_2-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 7_8_2-build: | - cd example.org - cabal build all - - 7_8_2-test: | - cd example.org - cabal test all --enable-tests - - 7_8_2-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 7.8.3 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--copy-fields=none' 'sourcehut' 'copy-fields-none.project' -# -# 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 -# -# REGENDATA ["--copy-fields=none","sourcehut","copy-fields-none.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-7.8.3 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 7_8_3-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.8.3 - - 7_8_3-check: | - cd example.org - cabal check - - 7_8_3-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 7_8_3-build: | - cd example.org - cabal build all - - 7_8_3-test: | - cd example.org - cabal test all --enable-tests - - 7_8_3-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 7.8.4 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--copy-fields=none' 'sourcehut' 'copy-fields-none.project' -# -# 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 -# -# REGENDATA ["--copy-fields=none","sourcehut","copy-fields-none.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-7.8.4 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 7_8_4-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.8.4 - - 7_8_4-check: | - cd example.org - cabal check - - 7_8_4-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 7_8_4-build: | - cd example.org - cabal build all - - 7_8_4-test: | - cd example.org - cabal test all --enable-tests - - 7_8_4-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.0.1 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--copy-fields=none' 'sourcehut' 'copy-fields-none.project' -# -# 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 -# -# REGENDATA ["--copy-fields=none","sourcehut","copy-fields-none.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.0.1 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_0_1-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.0.1 - - 8_0_1-check: | - cd example.org - cabal check - - 8_0_1-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_0_1-build: | - cd example.org - cabal build all - - 8_0_1-test: | - cd example.org - cabal test all --enable-tests - - 8_0_1-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.0.2 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--copy-fields=none' 'sourcehut' 'copy-fields-none.project' -# -# 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 -# -# REGENDATA ["--copy-fields=none","sourcehut","copy-fields-none.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.0.2 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_0_2-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.0.2 - - 8_0_2-check: | - cd example.org - cabal check - - 8_0_2-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_0_2-build: | - cd example.org - cabal build all - - 8_0_2-test: | - cd example.org - cabal test all --enable-tests - - 8_0_2-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.10.1 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--copy-fields=none' 'sourcehut' 'copy-fields-none.project' -# -# 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 -# -# REGENDATA ["--copy-fields=none","sourcehut","copy-fields-none.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.10.1 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_10_1-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.1 - - 8_10_1-check: | - cd example.org - cabal check - - 8_10_1-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_10_1-build: | - cd example.org - cabal build all - - 8_10_1-test: | - cd example.org - cabal test all --enable-tests - - 8_10_1-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.10.2 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--copy-fields=none' 'sourcehut' 'copy-fields-none.project' -# -# 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 -# -# REGENDATA ["--copy-fields=none","sourcehut","copy-fields-none.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.10.2 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_10_2-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.2 - - 8_10_2-check: | - cd example.org - cabal check - - 8_10_2-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_10_2-build: | - cd example.org - cabal build all - - 8_10_2-test: | - cd example.org - cabal test all --enable-tests - - 8_10_2-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.10.3 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--copy-fields=none' 'sourcehut' 'copy-fields-none.project' -# -# 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 -# -# REGENDATA ["--copy-fields=none","sourcehut","copy-fields-none.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.10.3 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_10_3-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.3 - - 8_10_3-check: | - cd example.org - cabal check - - 8_10_3-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_10_3-build: | - cd example.org - cabal build all - - 8_10_3-test: | - cd example.org - cabal test all --enable-tests - - 8_10_3-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.10.4 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--copy-fields=none' 'sourcehut' 'copy-fields-none.project' -# -# 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 -# -# REGENDATA ["--copy-fields=none","sourcehut","copy-fields-none.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.10.4 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_10_4-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.4 - - 8_10_4-check: | - cd example.org - cabal check - - 8_10_4-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_10_4-build: | - cd example.org - cabal build all - - 8_10_4-test: | - cd example.org - cabal test all --enable-tests - - 8_10_4-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.10.5 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--copy-fields=none' 'sourcehut' 'copy-fields-none.project' -# -# 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 -# -# REGENDATA ["--copy-fields=none","sourcehut","copy-fields-none.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.10.5 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_10_5-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.5 - - 8_10_5-check: | - cd example.org - cabal check - - 8_10_5-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_10_5-build: | - cd example.org - cabal build all - - 8_10_5-test: | - cd example.org - cabal test all --enable-tests - - 8_10_5-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.10.6 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--copy-fields=none' 'sourcehut' 'copy-fields-none.project' -# -# 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 -# -# REGENDATA ["--copy-fields=none","sourcehut","copy-fields-none.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.10.6 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_10_6-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.6 - - 8_10_6-check: | - cd example.org - cabal check - - 8_10_6-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_10_6-build: | - cd example.org - cabal build all - - 8_10_6-test: | - cd example.org - cabal test all --enable-tests - - 8_10_6-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.10.7 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--copy-fields=none' 'sourcehut' 'copy-fields-none.project' -# -# 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 -# -# REGENDATA ["--copy-fields=none","sourcehut","copy-fields-none.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.10.7 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_10_7-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.7 - - 8_10_7-check: | - cd example.org - cabal check - - 8_10_7-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_10_7-build: | - cd example.org - cabal build all - - 8_10_7-test: | - cd example.org - cabal test all --enable-tests - - 8_10_7-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.2.1 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--copy-fields=none' 'sourcehut' 'copy-fields-none.project' -# -# 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 -# -# REGENDATA ["--copy-fields=none","sourcehut","copy-fields-none.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.2.1 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_2_1-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.2.1 - - 8_2_1-check: | - cd example.org - cabal check - - 8_2_1-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_2_1-build: | - cd example.org - cabal build all - - 8_2_1-test: | - cd example.org - cabal test all --enable-tests - - 8_2_1-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.2.2 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--copy-fields=none' 'sourcehut' 'copy-fields-none.project' -# -# 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 -# -# REGENDATA ["--copy-fields=none","sourcehut","copy-fields-none.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.2.2 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_2_2-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.2.2 - - 8_2_2-check: | - cd example.org - cabal check - - 8_2_2-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_2_2-build: | - cd example.org - cabal build all - - 8_2_2-test: | - cd example.org - cabal test all --enable-tests - - 8_2_2-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.4.1 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--copy-fields=none' 'sourcehut' 'copy-fields-none.project' -# -# 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 -# -# REGENDATA ["--copy-fields=none","sourcehut","copy-fields-none.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.4.1 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_4_1-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.4.1 - - 8_4_1-check: | - cd example.org - cabal check - - 8_4_1-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_4_1-build: | - cd example.org - cabal build all - - 8_4_1-test: | - cd example.org - cabal test all --enable-tests - - 8_4_1-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.4.2 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--copy-fields=none' 'sourcehut' 'copy-fields-none.project' -# -# 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 -# -# REGENDATA ["--copy-fields=none","sourcehut","copy-fields-none.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.4.2 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_4_2-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.4.2 - - 8_4_2-check: | - cd example.org - cabal check - - 8_4_2-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_4_2-build: | - cd example.org - cabal build all - - 8_4_2-test: | - cd example.org - cabal test all --enable-tests - - 8_4_2-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.4.3 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--copy-fields=none' 'sourcehut' 'copy-fields-none.project' -# -# 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 -# -# REGENDATA ["--copy-fields=none","sourcehut","copy-fields-none.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.4.3 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_4_3-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.4.3 - - 8_4_3-check: | - cd example.org - cabal check - - 8_4_3-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_4_3-build: | - cd example.org - cabal build all - - 8_4_3-test: | - cd example.org - cabal test all --enable-tests - - 8_4_3-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.4.4 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--copy-fields=none' 'sourcehut' 'copy-fields-none.project' -# -# 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 -# -# REGENDATA ["--copy-fields=none","sourcehut","copy-fields-none.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.4.4 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_4_4-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.4.4 - - 8_4_4-check: | - cd example.org - cabal check - - 8_4_4-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_4_4-build: | - cd example.org - cabal build all - - 8_4_4-test: | - cd example.org - cabal test all --enable-tests - - 8_4_4-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.6.1 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--copy-fields=none' 'sourcehut' 'copy-fields-none.project' -# -# 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 -# -# REGENDATA ["--copy-fields=none","sourcehut","copy-fields-none.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.6.1 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_6_1-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.6.1 - - 8_6_1-check: | - cd example.org - cabal check - - 8_6_1-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_6_1-build: | - cd example.org - cabal build all - - 8_6_1-test: | - cd example.org - cabal test all --enable-tests - - 8_6_1-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.6.2 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--copy-fields=none' 'sourcehut' 'copy-fields-none.project' -# -# 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 -# -# REGENDATA ["--copy-fields=none","sourcehut","copy-fields-none.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.6.2 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_6_2-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.6.2 - - 8_6_2-check: | - cd example.org - cabal check - - 8_6_2-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_6_2-build: | - cd example.org - cabal build all - - 8_6_2-test: | - cd example.org - cabal test all --enable-tests - - 8_6_2-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.6.3 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--copy-fields=none' 'sourcehut' 'copy-fields-none.project' -# -# 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 -# -# REGENDATA ["--copy-fields=none","sourcehut","copy-fields-none.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.6.3 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_6_3-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.6.3 - - 8_6_3-check: | - cd example.org - cabal check - - 8_6_3-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_6_3-build: | - cd example.org - cabal build all - - 8_6_3-test: | - cd example.org - cabal test all --enable-tests - - 8_6_3-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.6.4 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--copy-fields=none' 'sourcehut' 'copy-fields-none.project' -# -# 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 -# -# REGENDATA ["--copy-fields=none","sourcehut","copy-fields-none.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.6.4 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_6_4-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.6.4 - - 8_6_4-check: | - cd example.org - cabal check - - 8_6_4-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_6_4-build: | - cd example.org - cabal build all - - 8_6_4-test: | - cd example.org - cabal test all --enable-tests - - 8_6_4-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.6.5 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--copy-fields=none' 'sourcehut' 'copy-fields-none.project' -# -# 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 -# -# REGENDATA ["--copy-fields=none","sourcehut","copy-fields-none.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.6.5 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_6_5-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.6.5 - - 8_6_5-check: | - cd example.org - cabal check - - 8_6_5-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_6_5-build: | - cd example.org - cabal build all - - 8_6_5-test: | - cd example.org - cabal test all --enable-tests - - 8_6_5-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.8.1 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--copy-fields=none' 'sourcehut' 'copy-fields-none.project' -# -# 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 -# -# REGENDATA ["--copy-fields=none","sourcehut","copy-fields-none.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.8.1 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_8_1-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.8.1 - - 8_8_1-check: | - cd example.org - cabal check - - 8_8_1-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_8_1-build: | - cd example.org - cabal build all - - 8_8_1-test: | - cd example.org - cabal test all --enable-tests - - 8_8_1-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.8.2 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--copy-fields=none' 'sourcehut' 'copy-fields-none.project' -# -# 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 -# -# REGENDATA ["--copy-fields=none","sourcehut","copy-fields-none.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.8.2 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_8_2-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.8.2 - - 8_8_2-check: | - cd example.org - cabal check - - 8_8_2-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_8_2-build: | - cd example.org - cabal build all - - 8_8_2-test: | - cd example.org - cabal test all --enable-tests - - 8_8_2-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.8.3 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--copy-fields=none' 'sourcehut' 'copy-fields-none.project' -# -# 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 -# -# REGENDATA ["--copy-fields=none","sourcehut","copy-fields-none.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.8.3 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_8_3-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.8.3 - - 8_8_3-check: | - cd example.org - cabal check - - 8_8_3-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_8_3-build: | - cd example.org - cabal build all - - 8_8_3-test: | - cd example.org - cabal test all --enable-tests - - 8_8_3-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.8.4 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--copy-fields=none' 'sourcehut' 'copy-fields-none.project' -# -# 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 -# -# REGENDATA ["--copy-fields=none","sourcehut","copy-fields-none.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.8.4 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_8_4-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.8.4 - - 8_8_4-check: | - cd example.org - cabal check - - 8_8_4-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_8_4-build: | - cd example.org - cabal build all - - 8_8_4-test: | - cd example.org - cabal test all --enable-tests - - 8_8_4-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com diff --git a/fixtures/copy-fields-none.travis b/fixtures/copy-fields-none.travis index b653543a..de8edfb2 100644 --- a/fixtures/copy-fields-none.travis +++ b/fixtures/copy-fields-none.travis @@ -2,7 +2,7 @@ # *INFO* Generating Travis-CI config for testing for GHC versions: 7.8.1 7.8.2 7.8.3 7.8.4 7.10.1 7.10.2 7.10.3 8.0.1 8.0.2 8.2.1 8.2.2 8.4.1 8.4.2 8.4.3 8.4.4 8.6.1 8.6.2 8.6.3 8.6.4 8.6.5 8.8.1 8.8.2 8.8.3 8.8.4 8.10.1 8.10.2 8.10.3 8.10.4 8.10.5 8.10.6 8.10.7 # This Travis job script has been generated by a script via # -# haskell-ci '--copy-fields=none' 'travis' 'copy-fields-none.project' +# haskell-ci '--copy-fields=none' 'travis' 'copy-fields-none.project' '--sourcehut-source' 'https://example.org' # # To regenerate the script (for example after adjusting tested-with) run # @@ -250,5 +250,5 @@ script: - rm -f cabal.project.local - ${CABAL} v2-build $WITHCOMPILER --disable-tests --disable-benchmarks all -# REGENDATA ["--copy-fields=none","travis","copy-fields-none.project"] +# REGENDATA ["--copy-fields=none","travis","copy-fields-none.project","--sourcehut-source","https://example.org"] # EOF diff --git a/fixtures/copy-fields-some.bash b/fixtures/copy-fields-some.bash index 78b1ec69..05aecaac 100644 --- a/fixtures/copy-fields-some.bash +++ b/fixtures/copy-fields-some.bash @@ -2,7 +2,7 @@ # *INFO* Generating Bash script for testing for GHC versions: 7.8.1 7.8.2 7.8.3 7.8.4 7.10.1 7.10.2 7.10.3 8.0.1 8.0.2 8.2.1 8.2.2 8.4.1 8.4.2 8.4.3 8.4.4 8.6.1 8.6.2 8.6.3 8.6.4 8.6.5 8.8.1 8.8.2 8.8.3 8.8.4 8.10.1 8.10.2 8.10.3 8.10.4 8.10.5 8.10.6 8.10.7 #!/bin/bash # shellcheck disable=SC2086,SC2016,SC2046 -# REGENDATA ["--copy-fields=some","bash","copy-fields-some.project"] +# REGENDATA ["--copy-fields=some","bash","copy-fields-some.project","--sourcehut-source","https://example.org"] set -o pipefail diff --git a/fixtures/copy-fields-some.github b/fixtures/copy-fields-some.github index 5948954a..295b9eb8 100644 --- a/fixtures/copy-fields-some.github +++ b/fixtures/copy-fields-some.github @@ -2,7 +2,7 @@ # *INFO* Generating GitHub config for testing for GHC versions: 7.8.1 7.8.2 7.8.3 7.8.4 7.10.1 7.10.2 7.10.3 8.0.1 8.0.2 8.2.1 8.2.2 8.4.1 8.4.2 8.4.3 8.4.4 8.6.1 8.6.2 8.6.3 8.6.4 8.6.5 8.8.1 8.8.2 8.8.3 8.8.4 8.10.1 8.10.2 8.10.3 8.10.4 8.10.5 8.10.6 8.10.7 # This GitHub workflow config has been generated by a script via # -# haskell-ci '--copy-fields=some' 'github' 'copy-fields-some.project' +# haskell-ci '--copy-fields=some' 'github' 'copy-fields-some.project' '--sourcehut-source' 'https://example.org' # # To regenerate the script (for example after adjusting tested-with) run # @@ -10,7 +10,7 @@ # # For more information, see https://github.com/haskell-CI/haskell-ci # -# REGENDATA ["--copy-fields=some","github","copy-fields-some.project"] +# REGENDATA ["--copy-fields=some","github","copy-fields-some.project","--sourcehut-source","https://example.org"] # name: Haskell-CI on: diff --git a/fixtures/copy-fields-some.sourcehut b/fixtures/copy-fields-some.sourcehut index bd2e1260..af721bc6 100644 --- a/fixtures/copy-fields-some.sourcehut +++ b/fixtures/copy-fields-some.sourcehut @@ -3,7 +3,7 @@ # manifest name: all # This Sourcehut job script has been generated by a script via # -# haskell-ci '--copy-fields=some' 'sourcehut' 'copy-fields-some.project' +# haskell-ci '--copy-fields=some' 'sourcehut' 'copy-fields-some.project' '--sourcehut-source' 'https://example.org' # # To regenerate the script (for example after adjusting tested-with) run # @@ -11,7 +11,7 @@ # # For more information, see https://github.com/haskell-CI/haskell-ci # -# REGENDATA ["--copy-fields=some","sourcehut","copy-fields-some.project"] +# REGENDATA ["--copy-fields=some","sourcehut","copy-fields-some.project","--sourcehut-source","https://example.org"] # image: ubuntu/bionic packages: diff --git a/fixtures/copy-fields-some.sourcehut-parallel b/fixtures/copy-fields-some.sourcehut-parallel deleted file mode 100644 index 39a3c3d8..00000000 --- a/fixtures/copy-fields-some.sourcehut-parallel +++ /dev/null @@ -1,1552 +0,0 @@ -# SUCCESS -# *INFO* Generating Sourcehut config for testing for GHC versions: 7.8.1 7.8.2 7.8.3 7.8.4 7.10.1 7.10.2 7.10.3 8.0.1 8.0.2 8.2.1 8.2.2 8.4.1 8.4.2 8.4.3 8.4.4 8.6.1 8.6.2 8.6.3 8.6.4 8.6.5 8.8.1 8.8.2 8.8.3 8.8.4 8.10.1 8.10.2 8.10.3 8.10.4 8.10.5 8.10.6 8.10.7 -# manifest name: 7.10.1 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--copy-fields=some' 'sourcehut' 'copy-fields-some.project' -# -# 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 -# -# REGENDATA ["--copy-fields=some","sourcehut","copy-fields-some.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-7.10.1 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 7_10_1-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.10.1 - - 7_10_1-check: | - cd example.org - cabal check - - 7_10_1-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 7_10_1-build: | - cd example.org - cabal build all - - 7_10_1-test: | - cd example.org - cabal test all --enable-tests - - 7_10_1-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 7.10.2 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--copy-fields=some' 'sourcehut' 'copy-fields-some.project' -# -# 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 -# -# REGENDATA ["--copy-fields=some","sourcehut","copy-fields-some.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-7.10.2 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 7_10_2-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.10.2 - - 7_10_2-check: | - cd example.org - cabal check - - 7_10_2-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 7_10_2-build: | - cd example.org - cabal build all - - 7_10_2-test: | - cd example.org - cabal test all --enable-tests - - 7_10_2-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 7.10.3 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--copy-fields=some' 'sourcehut' 'copy-fields-some.project' -# -# 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 -# -# REGENDATA ["--copy-fields=some","sourcehut","copy-fields-some.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-7.10.3 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 7_10_3-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.10.3 - - 7_10_3-check: | - cd example.org - cabal check - - 7_10_3-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 7_10_3-build: | - cd example.org - cabal build all - - 7_10_3-test: | - cd example.org - cabal test all --enable-tests - - 7_10_3-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 7.8.1 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--copy-fields=some' 'sourcehut' 'copy-fields-some.project' -# -# 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 -# -# REGENDATA ["--copy-fields=some","sourcehut","copy-fields-some.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-7.8.1 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 7_8_1-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.8.1 - - 7_8_1-check: | - cd example.org - cabal check - - 7_8_1-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 7_8_1-build: | - cd example.org - cabal build all - - 7_8_1-test: | - cd example.org - cabal test all --enable-tests - - 7_8_1-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 7.8.2 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--copy-fields=some' 'sourcehut' 'copy-fields-some.project' -# -# 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 -# -# REGENDATA ["--copy-fields=some","sourcehut","copy-fields-some.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-7.8.2 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 7_8_2-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.8.2 - - 7_8_2-check: | - cd example.org - cabal check - - 7_8_2-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 7_8_2-build: | - cd example.org - cabal build all - - 7_8_2-test: | - cd example.org - cabal test all --enable-tests - - 7_8_2-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 7.8.3 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--copy-fields=some' 'sourcehut' 'copy-fields-some.project' -# -# 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 -# -# REGENDATA ["--copy-fields=some","sourcehut","copy-fields-some.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-7.8.3 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 7_8_3-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.8.3 - - 7_8_3-check: | - cd example.org - cabal check - - 7_8_3-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 7_8_3-build: | - cd example.org - cabal build all - - 7_8_3-test: | - cd example.org - cabal test all --enable-tests - - 7_8_3-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 7.8.4 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--copy-fields=some' 'sourcehut' 'copy-fields-some.project' -# -# 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 -# -# REGENDATA ["--copy-fields=some","sourcehut","copy-fields-some.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-7.8.4 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 7_8_4-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.8.4 - - 7_8_4-check: | - cd example.org - cabal check - - 7_8_4-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 7_8_4-build: | - cd example.org - cabal build all - - 7_8_4-test: | - cd example.org - cabal test all --enable-tests - - 7_8_4-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.0.1 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--copy-fields=some' 'sourcehut' 'copy-fields-some.project' -# -# 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 -# -# REGENDATA ["--copy-fields=some","sourcehut","copy-fields-some.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.0.1 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_0_1-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.0.1 - - 8_0_1-check: | - cd example.org - cabal check - - 8_0_1-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_0_1-build: | - cd example.org - cabal build all - - 8_0_1-test: | - cd example.org - cabal test all --enable-tests - - 8_0_1-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.0.2 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--copy-fields=some' 'sourcehut' 'copy-fields-some.project' -# -# 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 -# -# REGENDATA ["--copy-fields=some","sourcehut","copy-fields-some.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.0.2 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_0_2-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.0.2 - - 8_0_2-check: | - cd example.org - cabal check - - 8_0_2-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_0_2-build: | - cd example.org - cabal build all - - 8_0_2-test: | - cd example.org - cabal test all --enable-tests - - 8_0_2-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.10.1 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--copy-fields=some' 'sourcehut' 'copy-fields-some.project' -# -# 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 -# -# REGENDATA ["--copy-fields=some","sourcehut","copy-fields-some.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.10.1 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_10_1-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.1 - - 8_10_1-check: | - cd example.org - cabal check - - 8_10_1-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_10_1-build: | - cd example.org - cabal build all - - 8_10_1-test: | - cd example.org - cabal test all --enable-tests - - 8_10_1-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.10.2 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--copy-fields=some' 'sourcehut' 'copy-fields-some.project' -# -# 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 -# -# REGENDATA ["--copy-fields=some","sourcehut","copy-fields-some.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.10.2 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_10_2-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.2 - - 8_10_2-check: | - cd example.org - cabal check - - 8_10_2-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_10_2-build: | - cd example.org - cabal build all - - 8_10_2-test: | - cd example.org - cabal test all --enable-tests - - 8_10_2-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.10.3 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--copy-fields=some' 'sourcehut' 'copy-fields-some.project' -# -# 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 -# -# REGENDATA ["--copy-fields=some","sourcehut","copy-fields-some.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.10.3 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_10_3-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.3 - - 8_10_3-check: | - cd example.org - cabal check - - 8_10_3-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_10_3-build: | - cd example.org - cabal build all - - 8_10_3-test: | - cd example.org - cabal test all --enable-tests - - 8_10_3-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.10.4 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--copy-fields=some' 'sourcehut' 'copy-fields-some.project' -# -# 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 -# -# REGENDATA ["--copy-fields=some","sourcehut","copy-fields-some.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.10.4 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_10_4-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.4 - - 8_10_4-check: | - cd example.org - cabal check - - 8_10_4-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_10_4-build: | - cd example.org - cabal build all - - 8_10_4-test: | - cd example.org - cabal test all --enable-tests - - 8_10_4-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.10.5 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--copy-fields=some' 'sourcehut' 'copy-fields-some.project' -# -# 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 -# -# REGENDATA ["--copy-fields=some","sourcehut","copy-fields-some.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.10.5 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_10_5-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.5 - - 8_10_5-check: | - cd example.org - cabal check - - 8_10_5-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_10_5-build: | - cd example.org - cabal build all - - 8_10_5-test: | - cd example.org - cabal test all --enable-tests - - 8_10_5-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.10.6 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--copy-fields=some' 'sourcehut' 'copy-fields-some.project' -# -# 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 -# -# REGENDATA ["--copy-fields=some","sourcehut","copy-fields-some.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.10.6 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_10_6-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.6 - - 8_10_6-check: | - cd example.org - cabal check - - 8_10_6-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_10_6-build: | - cd example.org - cabal build all - - 8_10_6-test: | - cd example.org - cabal test all --enable-tests - - 8_10_6-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.10.7 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--copy-fields=some' 'sourcehut' 'copy-fields-some.project' -# -# 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 -# -# REGENDATA ["--copy-fields=some","sourcehut","copy-fields-some.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.10.7 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_10_7-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.7 - - 8_10_7-check: | - cd example.org - cabal check - - 8_10_7-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_10_7-build: | - cd example.org - cabal build all - - 8_10_7-test: | - cd example.org - cabal test all --enable-tests - - 8_10_7-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.2.1 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--copy-fields=some' 'sourcehut' 'copy-fields-some.project' -# -# 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 -# -# REGENDATA ["--copy-fields=some","sourcehut","copy-fields-some.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.2.1 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_2_1-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.2.1 - - 8_2_1-check: | - cd example.org - cabal check - - 8_2_1-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_2_1-build: | - cd example.org - cabal build all - - 8_2_1-test: | - cd example.org - cabal test all --enable-tests - - 8_2_1-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.2.2 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--copy-fields=some' 'sourcehut' 'copy-fields-some.project' -# -# 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 -# -# REGENDATA ["--copy-fields=some","sourcehut","copy-fields-some.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.2.2 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_2_2-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.2.2 - - 8_2_2-check: | - cd example.org - cabal check - - 8_2_2-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_2_2-build: | - cd example.org - cabal build all - - 8_2_2-test: | - cd example.org - cabal test all --enable-tests - - 8_2_2-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.4.1 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--copy-fields=some' 'sourcehut' 'copy-fields-some.project' -# -# 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 -# -# REGENDATA ["--copy-fields=some","sourcehut","copy-fields-some.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.4.1 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_4_1-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.4.1 - - 8_4_1-check: | - cd example.org - cabal check - - 8_4_1-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_4_1-build: | - cd example.org - cabal build all - - 8_4_1-test: | - cd example.org - cabal test all --enable-tests - - 8_4_1-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.4.2 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--copy-fields=some' 'sourcehut' 'copy-fields-some.project' -# -# 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 -# -# REGENDATA ["--copy-fields=some","sourcehut","copy-fields-some.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.4.2 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_4_2-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.4.2 - - 8_4_2-check: | - cd example.org - cabal check - - 8_4_2-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_4_2-build: | - cd example.org - cabal build all - - 8_4_2-test: | - cd example.org - cabal test all --enable-tests - - 8_4_2-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.4.3 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--copy-fields=some' 'sourcehut' 'copy-fields-some.project' -# -# 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 -# -# REGENDATA ["--copy-fields=some","sourcehut","copy-fields-some.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.4.3 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_4_3-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.4.3 - - 8_4_3-check: | - cd example.org - cabal check - - 8_4_3-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_4_3-build: | - cd example.org - cabal build all - - 8_4_3-test: | - cd example.org - cabal test all --enable-tests - - 8_4_3-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.4.4 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--copy-fields=some' 'sourcehut' 'copy-fields-some.project' -# -# 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 -# -# REGENDATA ["--copy-fields=some","sourcehut","copy-fields-some.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.4.4 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_4_4-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.4.4 - - 8_4_4-check: | - cd example.org - cabal check - - 8_4_4-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_4_4-build: | - cd example.org - cabal build all - - 8_4_4-test: | - cd example.org - cabal test all --enable-tests - - 8_4_4-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.6.1 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--copy-fields=some' 'sourcehut' 'copy-fields-some.project' -# -# 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 -# -# REGENDATA ["--copy-fields=some","sourcehut","copy-fields-some.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.6.1 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_6_1-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.6.1 - - 8_6_1-check: | - cd example.org - cabal check - - 8_6_1-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_6_1-build: | - cd example.org - cabal build all - - 8_6_1-test: | - cd example.org - cabal test all --enable-tests - - 8_6_1-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.6.2 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--copy-fields=some' 'sourcehut' 'copy-fields-some.project' -# -# 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 -# -# REGENDATA ["--copy-fields=some","sourcehut","copy-fields-some.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.6.2 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_6_2-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.6.2 - - 8_6_2-check: | - cd example.org - cabal check - - 8_6_2-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_6_2-build: | - cd example.org - cabal build all - - 8_6_2-test: | - cd example.org - cabal test all --enable-tests - - 8_6_2-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.6.3 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--copy-fields=some' 'sourcehut' 'copy-fields-some.project' -# -# 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 -# -# REGENDATA ["--copy-fields=some","sourcehut","copy-fields-some.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.6.3 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_6_3-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.6.3 - - 8_6_3-check: | - cd example.org - cabal check - - 8_6_3-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_6_3-build: | - cd example.org - cabal build all - - 8_6_3-test: | - cd example.org - cabal test all --enable-tests - - 8_6_3-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.6.4 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--copy-fields=some' 'sourcehut' 'copy-fields-some.project' -# -# 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 -# -# REGENDATA ["--copy-fields=some","sourcehut","copy-fields-some.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.6.4 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_6_4-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.6.4 - - 8_6_4-check: | - cd example.org - cabal check - - 8_6_4-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_6_4-build: | - cd example.org - cabal build all - - 8_6_4-test: | - cd example.org - cabal test all --enable-tests - - 8_6_4-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.6.5 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--copy-fields=some' 'sourcehut' 'copy-fields-some.project' -# -# 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 -# -# REGENDATA ["--copy-fields=some","sourcehut","copy-fields-some.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.6.5 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_6_5-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.6.5 - - 8_6_5-check: | - cd example.org - cabal check - - 8_6_5-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_6_5-build: | - cd example.org - cabal build all - - 8_6_5-test: | - cd example.org - cabal test all --enable-tests - - 8_6_5-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.8.1 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--copy-fields=some' 'sourcehut' 'copy-fields-some.project' -# -# 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 -# -# REGENDATA ["--copy-fields=some","sourcehut","copy-fields-some.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.8.1 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_8_1-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.8.1 - - 8_8_1-check: | - cd example.org - cabal check - - 8_8_1-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_8_1-build: | - cd example.org - cabal build all - - 8_8_1-test: | - cd example.org - cabal test all --enable-tests - - 8_8_1-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.8.2 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--copy-fields=some' 'sourcehut' 'copy-fields-some.project' -# -# 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 -# -# REGENDATA ["--copy-fields=some","sourcehut","copy-fields-some.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.8.2 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_8_2-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.8.2 - - 8_8_2-check: | - cd example.org - cabal check - - 8_8_2-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_8_2-build: | - cd example.org - cabal build all - - 8_8_2-test: | - cd example.org - cabal test all --enable-tests - - 8_8_2-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.8.3 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--copy-fields=some' 'sourcehut' 'copy-fields-some.project' -# -# 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 -# -# REGENDATA ["--copy-fields=some","sourcehut","copy-fields-some.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.8.3 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_8_3-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.8.3 - - 8_8_3-check: | - cd example.org - cabal check - - 8_8_3-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_8_3-build: | - cd example.org - cabal build all - - 8_8_3-test: | - cd example.org - cabal test all --enable-tests - - 8_8_3-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.8.4 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--copy-fields=some' 'sourcehut' 'copy-fields-some.project' -# -# 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 -# -# REGENDATA ["--copy-fields=some","sourcehut","copy-fields-some.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.8.4 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_8_4-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.8.4 - - 8_8_4-check: | - cd example.org - cabal check - - 8_8_4-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_8_4-build: | - cd example.org - cabal build all - - 8_8_4-test: | - cd example.org - cabal test all --enable-tests - - 8_8_4-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com diff --git a/fixtures/copy-fields-some.travis b/fixtures/copy-fields-some.travis index 5fbc55e2..73aa458f 100644 --- a/fixtures/copy-fields-some.travis +++ b/fixtures/copy-fields-some.travis @@ -2,7 +2,7 @@ # *INFO* Generating Travis-CI config for testing for GHC versions: 7.8.1 7.8.2 7.8.3 7.8.4 7.10.1 7.10.2 7.10.3 8.0.1 8.0.2 8.2.1 8.2.2 8.4.1 8.4.2 8.4.3 8.4.4 8.6.1 8.6.2 8.6.3 8.6.4 8.6.5 8.8.1 8.8.2 8.8.3 8.8.4 8.10.1 8.10.2 8.10.3 8.10.4 8.10.5 8.10.6 8.10.7 # This Travis job script has been generated by a script via # -# haskell-ci '--copy-fields=some' 'travis' 'copy-fields-some.project' +# haskell-ci '--copy-fields=some' 'travis' 'copy-fields-some.project' '--sourcehut-source' 'https://example.org' # # To regenerate the script (for example after adjusting tested-with) run # @@ -256,5 +256,5 @@ script: - rm -f cabal.project.local - ${CABAL} v2-build $WITHCOMPILER --disable-tests --disable-benchmarks all -# REGENDATA ["--copy-fields=some","travis","copy-fields-some.project"] +# REGENDATA ["--copy-fields=some","travis","copy-fields-some.project","--sourcehut-source","https://example.org"] # EOF diff --git a/fixtures/empty-line.bash b/fixtures/empty-line.bash index f0337f9b..9a435f9f 100644 --- a/fixtures/empty-line.bash +++ b/fixtures/empty-line.bash @@ -2,7 +2,7 @@ # *INFO* Generating Bash script for testing for GHC versions: ghc-head 7.8.1 7.8.2 7.8.3 7.8.4 7.10.1 7.10.2 7.10.3 8.0.1 8.0.2 8.2.1 8.2.2 8.4.1 8.4.2 8.4.3 8.4.4 8.6.1 8.6.2 8.6.3 8.6.4 8.6.5 8.8.1 8.8.2 8.8.3 8.8.4 8.10.1 8.10.2 8.10.3 8.10.4 8.10.5 8.10.6 8.10.7 #!/bin/bash # shellcheck disable=SC2086,SC2016,SC2046 -# REGENDATA ["--ghc-head","bash","empty-line.project"] +# REGENDATA ["--ghc-head","bash","empty-line.project","--sourcehut-source","https://example.org"] set -o pipefail diff --git a/fixtures/empty-line.github b/fixtures/empty-line.github index ca3b9368..0c09e255 100644 --- a/fixtures/empty-line.github +++ b/fixtures/empty-line.github @@ -2,7 +2,7 @@ # *INFO* Generating GitHub config for testing for GHC versions: ghc-head 7.8.1 7.8.2 7.8.3 7.8.4 7.10.1 7.10.2 7.10.3 8.0.1 8.0.2 8.2.1 8.2.2 8.4.1 8.4.2 8.4.3 8.4.4 8.6.1 8.6.2 8.6.3 8.6.4 8.6.5 8.8.1 8.8.2 8.8.3 8.8.4 8.10.1 8.10.2 8.10.3 8.10.4 8.10.5 8.10.6 8.10.7 # This GitHub workflow config has been generated by a script via # -# haskell-ci '--ghc-head' 'github' 'empty-line.project' +# haskell-ci '--ghc-head' 'github' 'empty-line.project' '--sourcehut-source' 'https://example.org' # # To regenerate the script (for example after adjusting tested-with) run # @@ -10,7 +10,7 @@ # # For more information, see https://github.com/haskell-CI/haskell-ci # -# REGENDATA ["--ghc-head","github","empty-line.project"] +# REGENDATA ["--ghc-head","github","empty-line.project","--sourcehut-source","https://example.org"] # name: Haskell-CI on: diff --git a/fixtures/empty-line.sourcehut b/fixtures/empty-line.sourcehut index f7c43dbf..463f6b1e 100644 --- a/fixtures/empty-line.sourcehut +++ b/fixtures/empty-line.sourcehut @@ -3,7 +3,7 @@ # manifest name: all # This Sourcehut job script has been generated by a script via # -# haskell-ci '--ghc-head' 'sourcehut' 'empty-line.project' +# haskell-ci '--ghc-head' 'sourcehut' 'empty-line.project' '--sourcehut-source' 'https://example.org' # # To regenerate the script (for example after adjusting tested-with) run # @@ -11,7 +11,7 @@ # # For more information, see https://github.com/haskell-CI/haskell-ci # -# REGENDATA ["--ghc-head","sourcehut","empty-line.project"] +# REGENDATA ["--ghc-head","sourcehut","empty-line.project","--sourcehut-source","https://example.org"] # image: ubuntu/bionic packages: diff --git a/fixtures/empty-line.sourcehut-parallel b/fixtures/empty-line.sourcehut-parallel deleted file mode 100644 index 2378067d..00000000 --- a/fixtures/empty-line.sourcehut-parallel +++ /dev/null @@ -1,1602 +0,0 @@ -# SUCCESS -# *INFO* Generating Sourcehut config for testing for GHC versions: ghc-head 7.8.1 7.8.2 7.8.3 7.8.4 7.10.1 7.10.2 7.10.3 8.0.1 8.0.2 8.2.1 8.2.2 8.4.1 8.4.2 8.4.3 8.4.4 8.6.1 8.6.2 8.6.3 8.6.4 8.6.5 8.8.1 8.8.2 8.8.3 8.8.4 8.10.1 8.10.2 8.10.3 8.10.4 8.10.5 8.10.6 8.10.7 -# manifest name: 7.10.1 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--ghc-head' 'sourcehut' 'empty-line.project' -# -# 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 -# -# REGENDATA ["--ghc-head","sourcehut","empty-line.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-7.10.1 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 7_10_1-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.10.1 - - 7_10_1-check: | - cd example.org - cabal check - - 7_10_1-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 7_10_1-build: | - cd example.org - cabal build all - - 7_10_1-test: | - cd example.org - cabal test all --enable-tests - - 7_10_1-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 7.10.2 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--ghc-head' 'sourcehut' 'empty-line.project' -# -# 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 -# -# REGENDATA ["--ghc-head","sourcehut","empty-line.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-7.10.2 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 7_10_2-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.10.2 - - 7_10_2-check: | - cd example.org - cabal check - - 7_10_2-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 7_10_2-build: | - cd example.org - cabal build all - - 7_10_2-test: | - cd example.org - cabal test all --enable-tests - - 7_10_2-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 7.10.3 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--ghc-head' 'sourcehut' 'empty-line.project' -# -# 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 -# -# REGENDATA ["--ghc-head","sourcehut","empty-line.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-7.10.3 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 7_10_3-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.10.3 - - 7_10_3-check: | - cd example.org - cabal check - - 7_10_3-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 7_10_3-build: | - cd example.org - cabal build all - - 7_10_3-test: | - cd example.org - cabal test all --enable-tests - - 7_10_3-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 7.8.1 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--ghc-head' 'sourcehut' 'empty-line.project' -# -# 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 -# -# REGENDATA ["--ghc-head","sourcehut","empty-line.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-7.8.1 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 7_8_1-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.8.1 - - 7_8_1-check: | - cd example.org - cabal check - - 7_8_1-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 7_8_1-build: | - cd example.org - cabal build all - - 7_8_1-test: | - cd example.org - cabal test all --enable-tests - - 7_8_1-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 7.8.2 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--ghc-head' 'sourcehut' 'empty-line.project' -# -# 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 -# -# REGENDATA ["--ghc-head","sourcehut","empty-line.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-7.8.2 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 7_8_2-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.8.2 - - 7_8_2-check: | - cd example.org - cabal check - - 7_8_2-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 7_8_2-build: | - cd example.org - cabal build all - - 7_8_2-test: | - cd example.org - cabal test all --enable-tests - - 7_8_2-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 7.8.3 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--ghc-head' 'sourcehut' 'empty-line.project' -# -# 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 -# -# REGENDATA ["--ghc-head","sourcehut","empty-line.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-7.8.3 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 7_8_3-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.8.3 - - 7_8_3-check: | - cd example.org - cabal check - - 7_8_3-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 7_8_3-build: | - cd example.org - cabal build all - - 7_8_3-test: | - cd example.org - cabal test all --enable-tests - - 7_8_3-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 7.8.4 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--ghc-head' 'sourcehut' 'empty-line.project' -# -# 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 -# -# REGENDATA ["--ghc-head","sourcehut","empty-line.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-7.8.4 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 7_8_4-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.8.4 - - 7_8_4-check: | - cd example.org - cabal check - - 7_8_4-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 7_8_4-build: | - cd example.org - cabal build all - - 7_8_4-test: | - cd example.org - cabal test all --enable-tests - - 7_8_4-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.0.1 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--ghc-head' 'sourcehut' 'empty-line.project' -# -# 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 -# -# REGENDATA ["--ghc-head","sourcehut","empty-line.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.0.1 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_0_1-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.0.1 - - 8_0_1-check: | - cd example.org - cabal check - - 8_0_1-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_0_1-build: | - cd example.org - cabal build all - - 8_0_1-test: | - cd example.org - cabal test all --enable-tests - - 8_0_1-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.0.2 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--ghc-head' 'sourcehut' 'empty-line.project' -# -# 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 -# -# REGENDATA ["--ghc-head","sourcehut","empty-line.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.0.2 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_0_2-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.0.2 - - 8_0_2-check: | - cd example.org - cabal check - - 8_0_2-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_0_2-build: | - cd example.org - cabal build all - - 8_0_2-test: | - cd example.org - cabal test all --enable-tests - - 8_0_2-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.10.1 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--ghc-head' 'sourcehut' 'empty-line.project' -# -# 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 -# -# REGENDATA ["--ghc-head","sourcehut","empty-line.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.10.1 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_10_1-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.1 - - 8_10_1-check: | - cd example.org - cabal check - - 8_10_1-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_10_1-build: | - cd example.org - cabal build all - - 8_10_1-test: | - cd example.org - cabal test all --enable-tests - - 8_10_1-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.10.2 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--ghc-head' 'sourcehut' 'empty-line.project' -# -# 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 -# -# REGENDATA ["--ghc-head","sourcehut","empty-line.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.10.2 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_10_2-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.2 - - 8_10_2-check: | - cd example.org - cabal check - - 8_10_2-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_10_2-build: | - cd example.org - cabal build all - - 8_10_2-test: | - cd example.org - cabal test all --enable-tests - - 8_10_2-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.10.3 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--ghc-head' 'sourcehut' 'empty-line.project' -# -# 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 -# -# REGENDATA ["--ghc-head","sourcehut","empty-line.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.10.3 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_10_3-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.3 - - 8_10_3-check: | - cd example.org - cabal check - - 8_10_3-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_10_3-build: | - cd example.org - cabal build all - - 8_10_3-test: | - cd example.org - cabal test all --enable-tests - - 8_10_3-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.10.4 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--ghc-head' 'sourcehut' 'empty-line.project' -# -# 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 -# -# REGENDATA ["--ghc-head","sourcehut","empty-line.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.10.4 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_10_4-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.4 - - 8_10_4-check: | - cd example.org - cabal check - - 8_10_4-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_10_4-build: | - cd example.org - cabal build all - - 8_10_4-test: | - cd example.org - cabal test all --enable-tests - - 8_10_4-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.10.5 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--ghc-head' 'sourcehut' 'empty-line.project' -# -# 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 -# -# REGENDATA ["--ghc-head","sourcehut","empty-line.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.10.5 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_10_5-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.5 - - 8_10_5-check: | - cd example.org - cabal check - - 8_10_5-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_10_5-build: | - cd example.org - cabal build all - - 8_10_5-test: | - cd example.org - cabal test all --enable-tests - - 8_10_5-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.10.6 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--ghc-head' 'sourcehut' 'empty-line.project' -# -# 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 -# -# REGENDATA ["--ghc-head","sourcehut","empty-line.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.10.6 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_10_6-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.6 - - 8_10_6-check: | - cd example.org - cabal check - - 8_10_6-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_10_6-build: | - cd example.org - cabal build all - - 8_10_6-test: | - cd example.org - cabal test all --enable-tests - - 8_10_6-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.10.7 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--ghc-head' 'sourcehut' 'empty-line.project' -# -# 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 -# -# REGENDATA ["--ghc-head","sourcehut","empty-line.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.10.7 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_10_7-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.7 - - 8_10_7-check: | - cd example.org - cabal check - - 8_10_7-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_10_7-build: | - cd example.org - cabal build all - - 8_10_7-test: | - cd example.org - cabal test all --enable-tests - - 8_10_7-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.2.1 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--ghc-head' 'sourcehut' 'empty-line.project' -# -# 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 -# -# REGENDATA ["--ghc-head","sourcehut","empty-line.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.2.1 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_2_1-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.2.1 - - 8_2_1-check: | - cd example.org - cabal check - - 8_2_1-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_2_1-build: | - cd example.org - cabal build all - - 8_2_1-test: | - cd example.org - cabal test all --enable-tests - - 8_2_1-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.2.2 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--ghc-head' 'sourcehut' 'empty-line.project' -# -# 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 -# -# REGENDATA ["--ghc-head","sourcehut","empty-line.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.2.2 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_2_2-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.2.2 - - 8_2_2-check: | - cd example.org - cabal check - - 8_2_2-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_2_2-build: | - cd example.org - cabal build all - - 8_2_2-test: | - cd example.org - cabal test all --enable-tests - - 8_2_2-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.4.1 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--ghc-head' 'sourcehut' 'empty-line.project' -# -# 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 -# -# REGENDATA ["--ghc-head","sourcehut","empty-line.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.4.1 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_4_1-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.4.1 - - 8_4_1-check: | - cd example.org - cabal check - - 8_4_1-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_4_1-build: | - cd example.org - cabal build all - - 8_4_1-test: | - cd example.org - cabal test all --enable-tests - - 8_4_1-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.4.2 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--ghc-head' 'sourcehut' 'empty-line.project' -# -# 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 -# -# REGENDATA ["--ghc-head","sourcehut","empty-line.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.4.2 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_4_2-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.4.2 - - 8_4_2-check: | - cd example.org - cabal check - - 8_4_2-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_4_2-build: | - cd example.org - cabal build all - - 8_4_2-test: | - cd example.org - cabal test all --enable-tests - - 8_4_2-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.4.3 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--ghc-head' 'sourcehut' 'empty-line.project' -# -# 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 -# -# REGENDATA ["--ghc-head","sourcehut","empty-line.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.4.3 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_4_3-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.4.3 - - 8_4_3-check: | - cd example.org - cabal check - - 8_4_3-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_4_3-build: | - cd example.org - cabal build all - - 8_4_3-test: | - cd example.org - cabal test all --enable-tests - - 8_4_3-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.4.4 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--ghc-head' 'sourcehut' 'empty-line.project' -# -# 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 -# -# REGENDATA ["--ghc-head","sourcehut","empty-line.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.4.4 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_4_4-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.4.4 - - 8_4_4-check: | - cd example.org - cabal check - - 8_4_4-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_4_4-build: | - cd example.org - cabal build all - - 8_4_4-test: | - cd example.org - cabal test all --enable-tests - - 8_4_4-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.6.1 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--ghc-head' 'sourcehut' 'empty-line.project' -# -# 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 -# -# REGENDATA ["--ghc-head","sourcehut","empty-line.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.6.1 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_6_1-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.6.1 - - 8_6_1-check: | - cd example.org - cabal check - - 8_6_1-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_6_1-build: | - cd example.org - cabal build all - - 8_6_1-test: | - cd example.org - cabal test all --enable-tests - - 8_6_1-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.6.2 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--ghc-head' 'sourcehut' 'empty-line.project' -# -# 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 -# -# REGENDATA ["--ghc-head","sourcehut","empty-line.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.6.2 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_6_2-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.6.2 - - 8_6_2-check: | - cd example.org - cabal check - - 8_6_2-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_6_2-build: | - cd example.org - cabal build all - - 8_6_2-test: | - cd example.org - cabal test all --enable-tests - - 8_6_2-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.6.3 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--ghc-head' 'sourcehut' 'empty-line.project' -# -# 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 -# -# REGENDATA ["--ghc-head","sourcehut","empty-line.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.6.3 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_6_3-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.6.3 - - 8_6_3-check: | - cd example.org - cabal check - - 8_6_3-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_6_3-build: | - cd example.org - cabal build all - - 8_6_3-test: | - cd example.org - cabal test all --enable-tests - - 8_6_3-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.6.4 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--ghc-head' 'sourcehut' 'empty-line.project' -# -# 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 -# -# REGENDATA ["--ghc-head","sourcehut","empty-line.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.6.4 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_6_4-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.6.4 - - 8_6_4-check: | - cd example.org - cabal check - - 8_6_4-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_6_4-build: | - cd example.org - cabal build all - - 8_6_4-test: | - cd example.org - cabal test all --enable-tests - - 8_6_4-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.6.5 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--ghc-head' 'sourcehut' 'empty-line.project' -# -# 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 -# -# REGENDATA ["--ghc-head","sourcehut","empty-line.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.6.5 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_6_5-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.6.5 - - 8_6_5-check: | - cd example.org - cabal check - - 8_6_5-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_6_5-build: | - cd example.org - cabal build all - - 8_6_5-test: | - cd example.org - cabal test all --enable-tests - - 8_6_5-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.8.1 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--ghc-head' 'sourcehut' 'empty-line.project' -# -# 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 -# -# REGENDATA ["--ghc-head","sourcehut","empty-line.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.8.1 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_8_1-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.8.1 - - 8_8_1-check: | - cd example.org - cabal check - - 8_8_1-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_8_1-build: | - cd example.org - cabal build all - - 8_8_1-test: | - cd example.org - cabal test all --enable-tests - - 8_8_1-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.8.2 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--ghc-head' 'sourcehut' 'empty-line.project' -# -# 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 -# -# REGENDATA ["--ghc-head","sourcehut","empty-line.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.8.2 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_8_2-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.8.2 - - 8_8_2-check: | - cd example.org - cabal check - - 8_8_2-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_8_2-build: | - cd example.org - cabal build all - - 8_8_2-test: | - cd example.org - cabal test all --enable-tests - - 8_8_2-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.8.3 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--ghc-head' 'sourcehut' 'empty-line.project' -# -# 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 -# -# REGENDATA ["--ghc-head","sourcehut","empty-line.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.8.3 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_8_3-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.8.3 - - 8_8_3-check: | - cd example.org - cabal check - - 8_8_3-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_8_3-build: | - cd example.org - cabal build all - - 8_8_3-test: | - cd example.org - cabal test all --enable-tests - - 8_8_3-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.8.4 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--ghc-head' 'sourcehut' 'empty-line.project' -# -# 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 -# -# REGENDATA ["--ghc-head","sourcehut","empty-line.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.8.4 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_8_4-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.8.4 - - 8_8_4-check: | - cd example.org - cabal check - - 8_8_4-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_8_4-build: | - cd example.org - cabal build all - - 8_8_4-test: | - cd example.org - cabal test all --enable-tests - - 8_8_4-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: ghc-head -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--ghc-head' 'sourcehut' 'empty-line.project' -# -# 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 -# -# REGENDATA ["--ghc-head","sourcehut","empty-line.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-head -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - ghc-head-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-head - - ghc-head-check: | - cd example.org - cabal check - - ghc-head-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - ghc-head-build: | - cd example.org - cabal build all - - ghc-head-test: | - cd example.org - cabal test all --enable-tests - - ghc-head-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com diff --git a/fixtures/empty-line.travis b/fixtures/empty-line.travis index 18a692d8..2bafaafb 100644 --- a/fixtures/empty-line.travis +++ b/fixtures/empty-line.travis @@ -2,7 +2,7 @@ # *INFO* Generating Travis-CI config for testing for GHC versions: ghc-head 7.8.1 7.8.2 7.8.3 7.8.4 7.10.1 7.10.2 7.10.3 8.0.1 8.0.2 8.2.1 8.2.2 8.4.1 8.4.2 8.4.3 8.4.4 8.6.1 8.6.2 8.6.3 8.6.4 8.6.5 8.8.1 8.8.2 8.8.3 8.8.4 8.10.1 8.10.2 8.10.3 8.10.4 8.10.5 8.10.6 8.10.7 # This Travis job script has been generated by a script via # -# haskell-ci '--ghc-head' 'travis' 'empty-line.project' +# haskell-ci '--ghc-head' 'travis' 'empty-line.project' '--sourcehut-source' 'https://example.org' # # To regenerate the script (for example after adjusting tested-with) run # @@ -281,5 +281,5 @@ script: - rm -f cabal.project.local - ${CABAL} v2-build $WITHCOMPILER --disable-tests --disable-benchmarks all -# REGENDATA ["--ghc-head","travis","empty-line.project"] +# REGENDATA ["--ghc-head","travis","empty-line.project","--sourcehut-source","https://example.org"] # EOF diff --git a/fixtures/enabled-jobs.bash b/fixtures/enabled-jobs.bash index 659b9e3a..ba36b602 100644 --- a/fixtures/enabled-jobs.bash +++ b/fixtures/enabled-jobs.bash @@ -2,7 +2,7 @@ # *INFO* Generating Bash script for testing for GHC versions: 8.0.1 8.0.2 8.2.1 8.2.2 8.4.1 8.4.2 8.4.3 8.4.4 8.6.1 8.6.2 8.6.3 8.6.4 8.6.5 8.8.1 8.8.2 8.8.3 8.8.4 8.10.1 8.10.2 8.10.3 8.10.4 8.10.5 8.10.6 8.10.7 9.0.1 9.0.2 9.2.1 9.2.2 9.2.3 9.4.1 ghcjs-8.4 #!/bin/bash # shellcheck disable=SC2086,SC2016,SC2046 -# REGENDATA ["--enabled-jobs=>=8","bash","enabled-jobs.project"] +# REGENDATA ["--enabled-jobs=>=8","bash","enabled-jobs.project","--sourcehut-source","https://example.org"] set -o pipefail diff --git a/fixtures/enabled-jobs.github b/fixtures/enabled-jobs.github index a5eded8c..2d5b6f75 100644 --- a/fixtures/enabled-jobs.github +++ b/fixtures/enabled-jobs.github @@ -2,7 +2,7 @@ # *INFO* Generating GitHub config for testing for GHC versions: 8.0.1 8.0.2 8.2.1 8.2.2 8.4.1 8.4.2 8.4.3 8.4.4 8.6.1 8.6.2 8.6.3 8.6.4 8.6.5 8.8.1 8.8.2 8.8.3 8.8.4 8.10.1 8.10.2 8.10.3 8.10.4 8.10.5 8.10.6 8.10.7 9.0.1 9.0.2 9.2.1 9.2.2 9.2.3 9.4.1 ghcjs-8.4 # This GitHub workflow config has been generated by a script via # -# haskell-ci '--enabled-jobs=>=8' 'github' 'enabled-jobs.project' +# haskell-ci '--enabled-jobs=>=8' 'github' 'enabled-jobs.project' '--sourcehut-source' 'https://example.org' # # To regenerate the script (for example after adjusting tested-with) run # @@ -10,7 +10,7 @@ # # For more information, see https://github.com/haskell-CI/haskell-ci # -# REGENDATA ["--enabled-jobs=>=8","github","enabled-jobs.project"] +# REGENDATA ["--enabled-jobs=>=8","github","enabled-jobs.project","--sourcehut-source","https://example.org"] # name: Haskell-CI on: diff --git a/fixtures/enabled-jobs.sourcehut b/fixtures/enabled-jobs.sourcehut index 942e6428..e8753cee 100644 --- a/fixtures/enabled-jobs.sourcehut +++ b/fixtures/enabled-jobs.sourcehut @@ -3,7 +3,7 @@ # manifest name: all # This Sourcehut job script has been generated by a script via # -# haskell-ci '--enabled-jobs=>=8' 'sourcehut' 'enabled-jobs.project' +# haskell-ci '--enabled-jobs=>=8' 'sourcehut' 'enabled-jobs.project' '--sourcehut-source' 'https://example.org' # # To regenerate the script (for example after adjusting tested-with) run # @@ -11,7 +11,7 @@ # # For more information, see https://github.com/haskell-CI/haskell-ci # -# REGENDATA ["--enabled-jobs=>=8","sourcehut","enabled-jobs.project"] +# REGENDATA ["--enabled-jobs=>=8","sourcehut","enabled-jobs.project","--sourcehut-source","https://example.org"] # image: ubuntu/bionic packages: diff --git a/fixtures/enabled-jobs.sourcehut-parallel b/fixtures/enabled-jobs.sourcehut-parallel deleted file mode 100644 index 856792cc..00000000 --- a/fixtures/enabled-jobs.sourcehut-parallel +++ /dev/null @@ -1,1352 +0,0 @@ -# SUCCESS -# *INFO* Generating Sourcehut config for testing for GHC versions: 8.0.1 8.0.2 8.2.1 8.2.2 8.4.1 8.4.2 8.4.3 8.4.4 8.6.1 8.6.2 8.6.3 8.6.4 8.6.5 8.8.1 8.8.2 8.8.3 8.8.4 8.10.1 8.10.2 8.10.3 8.10.4 8.10.5 8.10.6 8.10.7 9.0.1 9.2.1 ghcjs-8.4 -# manifest name: 8.0.1 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--enabled-jobs=>=8' 'sourcehut' 'enabled-jobs.project' -# -# 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 -# -# REGENDATA ["--enabled-jobs=>=8","sourcehut","enabled-jobs.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.0.1 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_0_1-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.0.1 - - 8_0_1-check: | - cd example.org - cabal check - - 8_0_1-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_0_1-build: | - cd example.org - cabal build all - - 8_0_1-test: | - cd example.org - cabal test all --enable-tests - - 8_0_1-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: Oleg Grenrus -# manifest name: 8.0.2 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--enabled-jobs=>=8' 'sourcehut' 'enabled-jobs.project' -# -# 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 -# -# REGENDATA ["--enabled-jobs=>=8","sourcehut","enabled-jobs.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.0.2 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_0_2-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.0.2 - - 8_0_2-check: | - cd example.org - cabal check - - 8_0_2-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_0_2-build: | - cd example.org - cabal build all - - 8_0_2-test: | - cd example.org - cabal test all --enable-tests - - 8_0_2-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: Oleg Grenrus -# manifest name: 8.10.1 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--enabled-jobs=>=8' 'sourcehut' 'enabled-jobs.project' -# -# 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 -# -# REGENDATA ["--enabled-jobs=>=8","sourcehut","enabled-jobs.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.10.1 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_10_1-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.1 - - 8_10_1-check: | - cd example.org - cabal check - - 8_10_1-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_10_1-build: | - cd example.org - cabal build all - - 8_10_1-test: | - cd example.org - cabal test all --enable-tests - - 8_10_1-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: Oleg Grenrus -# manifest name: 8.10.2 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--enabled-jobs=>=8' 'sourcehut' 'enabled-jobs.project' -# -# 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 -# -# REGENDATA ["--enabled-jobs=>=8","sourcehut","enabled-jobs.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.10.2 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_10_2-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.2 - - 8_10_2-check: | - cd example.org - cabal check - - 8_10_2-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_10_2-build: | - cd example.org - cabal build all - - 8_10_2-test: | - cd example.org - cabal test all --enable-tests - - 8_10_2-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: Oleg Grenrus -# manifest name: 8.10.3 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--enabled-jobs=>=8' 'sourcehut' 'enabled-jobs.project' -# -# 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 -# -# REGENDATA ["--enabled-jobs=>=8","sourcehut","enabled-jobs.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.10.3 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_10_3-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.3 - - 8_10_3-check: | - cd example.org - cabal check - - 8_10_3-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_10_3-build: | - cd example.org - cabal build all - - 8_10_3-test: | - cd example.org - cabal test all --enable-tests - - 8_10_3-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: Oleg Grenrus -# manifest name: 8.10.4 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--enabled-jobs=>=8' 'sourcehut' 'enabled-jobs.project' -# -# 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 -# -# REGENDATA ["--enabled-jobs=>=8","sourcehut","enabled-jobs.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.10.4 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_10_4-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.4 - - 8_10_4-check: | - cd example.org - cabal check - - 8_10_4-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_10_4-build: | - cd example.org - cabal build all - - 8_10_4-test: | - cd example.org - cabal test all --enable-tests - - 8_10_4-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: Oleg Grenrus -# manifest name: 8.10.5 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--enabled-jobs=>=8' 'sourcehut' 'enabled-jobs.project' -# -# 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 -# -# REGENDATA ["--enabled-jobs=>=8","sourcehut","enabled-jobs.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.10.5 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_10_5-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.5 - - 8_10_5-check: | - cd example.org - cabal check - - 8_10_5-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_10_5-build: | - cd example.org - cabal build all - - 8_10_5-test: | - cd example.org - cabal test all --enable-tests - - 8_10_5-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: Oleg Grenrus -# manifest name: 8.10.6 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--enabled-jobs=>=8' 'sourcehut' 'enabled-jobs.project' -# -# 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 -# -# REGENDATA ["--enabled-jobs=>=8","sourcehut","enabled-jobs.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.10.6 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_10_6-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.6 - - 8_10_6-check: | - cd example.org - cabal check - - 8_10_6-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_10_6-build: | - cd example.org - cabal build all - - 8_10_6-test: | - cd example.org - cabal test all --enable-tests - - 8_10_6-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: Oleg Grenrus -# manifest name: 8.10.7 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--enabled-jobs=>=8' 'sourcehut' 'enabled-jobs.project' -# -# 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 -# -# REGENDATA ["--enabled-jobs=>=8","sourcehut","enabled-jobs.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.10.7 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_10_7-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.7 - - 8_10_7-check: | - cd example.org - cabal check - - 8_10_7-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_10_7-build: | - cd example.org - cabal build all - - 8_10_7-test: | - cd example.org - cabal test all --enable-tests - - 8_10_7-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: Oleg Grenrus -# manifest name: 8.2.1 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--enabled-jobs=>=8' 'sourcehut' 'enabled-jobs.project' -# -# 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 -# -# REGENDATA ["--enabled-jobs=>=8","sourcehut","enabled-jobs.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.2.1 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_2_1-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.2.1 - - 8_2_1-check: | - cd example.org - cabal check - - 8_2_1-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_2_1-build: | - cd example.org - cabal build all - - 8_2_1-test: | - cd example.org - cabal test all --enable-tests - - 8_2_1-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: Oleg Grenrus -# manifest name: 8.2.2 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--enabled-jobs=>=8' 'sourcehut' 'enabled-jobs.project' -# -# 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 -# -# REGENDATA ["--enabled-jobs=>=8","sourcehut","enabled-jobs.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.2.2 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_2_2-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.2.2 - - 8_2_2-check: | - cd example.org - cabal check - - 8_2_2-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_2_2-build: | - cd example.org - cabal build all - - 8_2_2-test: | - cd example.org - cabal test all --enable-tests - - 8_2_2-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: Oleg Grenrus -# manifest name: 8.4.1 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--enabled-jobs=>=8' 'sourcehut' 'enabled-jobs.project' -# -# 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 -# -# REGENDATA ["--enabled-jobs=>=8","sourcehut","enabled-jobs.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.4.1 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_4_1-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.4.1 - - 8_4_1-check: | - cd example.org - cabal check - - 8_4_1-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_4_1-build: | - cd example.org - cabal build all - - 8_4_1-test: | - cd example.org - cabal test all --enable-tests - - 8_4_1-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: Oleg Grenrus -# manifest name: 8.4.2 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--enabled-jobs=>=8' 'sourcehut' 'enabled-jobs.project' -# -# 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 -# -# REGENDATA ["--enabled-jobs=>=8","sourcehut","enabled-jobs.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.4.2 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_4_2-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.4.2 - - 8_4_2-check: | - cd example.org - cabal check - - 8_4_2-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_4_2-build: | - cd example.org - cabal build all - - 8_4_2-test: | - cd example.org - cabal test all --enable-tests - - 8_4_2-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: Oleg Grenrus -# manifest name: 8.4.3 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--enabled-jobs=>=8' 'sourcehut' 'enabled-jobs.project' -# -# 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 -# -# REGENDATA ["--enabled-jobs=>=8","sourcehut","enabled-jobs.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.4.3 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_4_3-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.4.3 - - 8_4_3-check: | - cd example.org - cabal check - - 8_4_3-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_4_3-build: | - cd example.org - cabal build all - - 8_4_3-test: | - cd example.org - cabal test all --enable-tests - - 8_4_3-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: Oleg Grenrus -# manifest name: 8.4.4 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--enabled-jobs=>=8' 'sourcehut' 'enabled-jobs.project' -# -# 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 -# -# REGENDATA ["--enabled-jobs=>=8","sourcehut","enabled-jobs.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.4.4 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_4_4-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.4.4 - - 8_4_4-check: | - cd example.org - cabal check - - 8_4_4-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_4_4-build: | - cd example.org - cabal build all - - 8_4_4-test: | - cd example.org - cabal test all --enable-tests - - 8_4_4-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: Oleg Grenrus -# manifest name: 8.6.1 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--enabled-jobs=>=8' 'sourcehut' 'enabled-jobs.project' -# -# 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 -# -# REGENDATA ["--enabled-jobs=>=8","sourcehut","enabled-jobs.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.6.1 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_6_1-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.6.1 - - 8_6_1-check: | - cd example.org - cabal check - - 8_6_1-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_6_1-build: | - cd example.org - cabal build all - - 8_6_1-test: | - cd example.org - cabal test all --enable-tests - - 8_6_1-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: Oleg Grenrus -# manifest name: 8.6.2 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--enabled-jobs=>=8' 'sourcehut' 'enabled-jobs.project' -# -# 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 -# -# REGENDATA ["--enabled-jobs=>=8","sourcehut","enabled-jobs.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.6.2 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_6_2-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.6.2 - - 8_6_2-check: | - cd example.org - cabal check - - 8_6_2-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_6_2-build: | - cd example.org - cabal build all - - 8_6_2-test: | - cd example.org - cabal test all --enable-tests - - 8_6_2-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: Oleg Grenrus -# manifest name: 8.6.3 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--enabled-jobs=>=8' 'sourcehut' 'enabled-jobs.project' -# -# 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 -# -# REGENDATA ["--enabled-jobs=>=8","sourcehut","enabled-jobs.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.6.3 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_6_3-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.6.3 - - 8_6_3-check: | - cd example.org - cabal check - - 8_6_3-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_6_3-build: | - cd example.org - cabal build all - - 8_6_3-test: | - cd example.org - cabal test all --enable-tests - - 8_6_3-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: Oleg Grenrus -# manifest name: 8.6.4 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--enabled-jobs=>=8' 'sourcehut' 'enabled-jobs.project' -# -# 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 -# -# REGENDATA ["--enabled-jobs=>=8","sourcehut","enabled-jobs.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.6.4 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_6_4-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.6.4 - - 8_6_4-check: | - cd example.org - cabal check - - 8_6_4-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_6_4-build: | - cd example.org - cabal build all - - 8_6_4-test: | - cd example.org - cabal test all --enable-tests - - 8_6_4-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: Oleg Grenrus -# manifest name: 8.6.5 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--enabled-jobs=>=8' 'sourcehut' 'enabled-jobs.project' -# -# 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 -# -# REGENDATA ["--enabled-jobs=>=8","sourcehut","enabled-jobs.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.6.5 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_6_5-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.6.5 - - 8_6_5-check: | - cd example.org - cabal check - - 8_6_5-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_6_5-build: | - cd example.org - cabal build all - - 8_6_5-test: | - cd example.org - cabal test all --enable-tests - - 8_6_5-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: Oleg Grenrus -# manifest name: 8.8.1 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--enabled-jobs=>=8' 'sourcehut' 'enabled-jobs.project' -# -# 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 -# -# REGENDATA ["--enabled-jobs=>=8","sourcehut","enabled-jobs.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.8.1 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_8_1-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.8.1 - - 8_8_1-check: | - cd example.org - cabal check - - 8_8_1-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_8_1-build: | - cd example.org - cabal build all - - 8_8_1-test: | - cd example.org - cabal test all --enable-tests - - 8_8_1-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: Oleg Grenrus -# manifest name: 8.8.2 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--enabled-jobs=>=8' 'sourcehut' 'enabled-jobs.project' -# -# 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 -# -# REGENDATA ["--enabled-jobs=>=8","sourcehut","enabled-jobs.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.8.2 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_8_2-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.8.2 - - 8_8_2-check: | - cd example.org - cabal check - - 8_8_2-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_8_2-build: | - cd example.org - cabal build all - - 8_8_2-test: | - cd example.org - cabal test all --enable-tests - - 8_8_2-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: Oleg Grenrus -# manifest name: 8.8.3 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--enabled-jobs=>=8' 'sourcehut' 'enabled-jobs.project' -# -# 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 -# -# REGENDATA ["--enabled-jobs=>=8","sourcehut","enabled-jobs.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.8.3 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_8_3-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.8.3 - - 8_8_3-check: | - cd example.org - cabal check - - 8_8_3-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_8_3-build: | - cd example.org - cabal build all - - 8_8_3-test: | - cd example.org - cabal test all --enable-tests - - 8_8_3-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: Oleg Grenrus -# manifest name: 8.8.4 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--enabled-jobs=>=8' 'sourcehut' 'enabled-jobs.project' -# -# 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 -# -# REGENDATA ["--enabled-jobs=>=8","sourcehut","enabled-jobs.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.8.4 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_8_4-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.8.4 - - 8_8_4-check: | - cd example.org - cabal check - - 8_8_4-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_8_4-build: | - cd example.org - cabal build all - - 8_8_4-test: | - cd example.org - cabal test all --enable-tests - - 8_8_4-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: Oleg Grenrus -# manifest name: 9.0.1 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--enabled-jobs=>=8' 'sourcehut' 'enabled-jobs.project' -# -# 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 -# -# REGENDATA ["--enabled-jobs=>=8","sourcehut","enabled-jobs.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-9.0.1 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 9_0_1-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-9.0.1 - - 9_0_1-check: | - cd example.org - cabal check - - 9_0_1-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 9_0_1-build: | - cd example.org - cabal build all - - 9_0_1-test: | - cd example.org - cabal test all --enable-tests - - 9_0_1-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: Oleg Grenrus -# manifest name: 9.2.1 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--enabled-jobs=>=8' 'sourcehut' 'enabled-jobs.project' -# -# 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 -# -# REGENDATA ["--enabled-jobs=>=8","sourcehut","enabled-jobs.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-9.2.1 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 9_2_1-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-9.2.1 - - 9_2_1-check: | - cd example.org - cabal check - - 9_2_1-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 9_2_1-build: | - cd example.org - cabal build all - - 9_2_1-test: | - cd example.org - cabal test all --enable-tests - - 9_2_1-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: Oleg Grenrus -# manifest name: ghcjs-8.4 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--enabled-jobs=>=8' 'sourcehut' 'enabled-jobs.project' -# -# 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 -# -# REGENDATA ["--enabled-jobs=>=8","sourcehut","enabled-jobs.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghcjs-8.4 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - ghcjs-8_4-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghcjs-8.4 - - ghcjs-8_4-check: | - cd example.org - cabal check - - ghcjs-8_4-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - ghcjs-8_4-build: | - cd example.org - cabal build all - - ghcjs-8_4-test: | - cd example.org - cabal test all --enable-tests - - ghcjs-8_4-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: Oleg Grenrus diff --git a/fixtures/enabled-jobs.travis b/fixtures/enabled-jobs.travis index 3869bb49..354a078c 100644 --- a/fixtures/enabled-jobs.travis +++ b/fixtures/enabled-jobs.travis @@ -2,7 +2,7 @@ # *INFO* Generating Travis-CI config for testing for GHC versions: 8.0.1 8.0.2 8.2.1 8.2.2 8.4.1 8.4.2 8.4.3 8.4.4 8.6.1 8.6.2 8.6.3 8.6.4 8.6.5 8.8.1 8.8.2 8.8.3 8.8.4 8.10.1 8.10.2 8.10.3 8.10.4 8.10.5 8.10.6 8.10.7 9.0.1 9.0.2 9.2.1 9.2.2 9.2.3 9.4.1 ghcjs-8.4 # This Travis job script has been generated by a script via # -# haskell-ci '--enabled-jobs=>=8' 'travis' 'enabled-jobs.project' +# haskell-ci '--enabled-jobs=>=8' 'travis' 'enabled-jobs.project' '--sourcehut-source' 'https://example.org' # # To regenerate the script (for example after adjusting tested-with) run # @@ -256,5 +256,5 @@ script: - rm -f cabal.project.local - ${CABAL} v2-build $WITHCOMPILER --disable-tests --disable-benchmarks all -# REGENDATA ["--enabled-jobs=>=8","travis","enabled-jobs.project"] +# REGENDATA ["--enabled-jobs=>=8","travis","enabled-jobs.project","--sourcehut-source","https://example.org"] # EOF diff --git a/fixtures/fail-versions.sourcehut-parallel b/fixtures/fail-versions.sourcehut-parallel deleted file mode 100644 index 0e629b61..00000000 --- a/fixtures/fail-versions.sourcehut-parallel +++ /dev/null @@ -1,3 +0,0 @@ -# FAILURE -# *ERROR* servant-client-core is missing tested-with annotations for: ghc-7.8.1,ghc-7.8.2,ghc-7.8.3,ghc-7.8.4 -# *ERROR* servant-foreign is missing tested-with annotations for: ghc-7.8.1,ghc-7.8.2,ghc-7.8.3,ghc-7.8.4 diff --git a/fixtures/irc-channels.bash b/fixtures/irc-channels.bash index daf1ef4c..519fd0a7 100644 --- a/fixtures/irc-channels.bash +++ b/fixtures/irc-channels.bash @@ -2,7 +2,7 @@ # *INFO* Generating Bash script for testing for GHC versions: 7.8.1 7.8.2 7.8.3 7.8.4 7.10.1 7.10.2 7.10.3 8.0.1 8.0.2 8.2.1 8.2.2 8.4.1 8.4.2 8.4.3 8.4.4 8.6.1 8.6.2 8.6.3 8.6.4 8.6.5 8.8.1 8.8.2 8.8.3 8.8.4 8.10.1 8.10.2 8.10.3 8.10.4 8.10.5 8.10.6 8.10.7 #!/bin/bash # shellcheck disable=SC2086,SC2016,SC2046 -# REGENDATA ["--irc-channels=irc.libera.chat#mychannel","bash","irc-channels.project"] +# REGENDATA ["--irc-channels=irc.libera.chat#mychannel","bash","irc-channels.project","--sourcehut-source","https://example.org"] set -o pipefail diff --git a/fixtures/irc-channels.github b/fixtures/irc-channels.github index 44547904..18135ca0 100644 --- a/fixtures/irc-channels.github +++ b/fixtures/irc-channels.github @@ -2,7 +2,7 @@ # *INFO* Generating GitHub config for testing for GHC versions: 7.8.1 7.8.2 7.8.3 7.8.4 7.10.1 7.10.2 7.10.3 8.0.1 8.0.2 8.2.1 8.2.2 8.4.1 8.4.2 8.4.3 8.4.4 8.6.1 8.6.2 8.6.3 8.6.4 8.6.5 8.8.1 8.8.2 8.8.3 8.8.4 8.10.1 8.10.2 8.10.3 8.10.4 8.10.5 8.10.6 8.10.7 # This GitHub workflow config has been generated by a script via # -# haskell-ci '--irc-channels=irc.libera.chat#mychannel' 'github' 'irc-channels.project' +# haskell-ci '--irc-channels=irc.libera.chat#mychannel' 'github' 'irc-channels.project' '--sourcehut-source' 'https://example.org' # # To regenerate the script (for example after adjusting tested-with) run # @@ -10,7 +10,7 @@ # # For more information, see https://github.com/haskell-CI/haskell-ci # -# REGENDATA ["--irc-channels=irc.libera.chat#mychannel","github","irc-channels.project"] +# REGENDATA ["--irc-channels=irc.libera.chat#mychannel","github","irc-channels.project","--sourcehut-source","https://example.org"] # name: Haskell-CI on: diff --git a/fixtures/irc-channels.sourcehut b/fixtures/irc-channels.sourcehut index 74c0ccff..8ab83ba1 100644 --- a/fixtures/irc-channels.sourcehut +++ b/fixtures/irc-channels.sourcehut @@ -3,7 +3,7 @@ # manifest name: all # This Sourcehut job script has been generated by a script via # -# haskell-ci '--irc-channels=irc.libera.chat#mychannel' 'sourcehut' 'irc-channels.project' +# haskell-ci '--irc-channels=irc.libera.chat#mychannel' 'sourcehut' 'irc-channels.project' '--sourcehut-source' 'https://example.org' # # To regenerate the script (for example after adjusting tested-with) run # @@ -11,7 +11,7 @@ # # For more information, see https://github.com/haskell-CI/haskell-ci # -# REGENDATA ["--irc-channels=irc.libera.chat#mychannel","sourcehut","irc-channels.project"] +# REGENDATA ["--irc-channels=irc.libera.chat#mychannel","sourcehut","irc-channels.project","--sourcehut-source","https://example.org"] # image: ubuntu/bionic packages: diff --git a/fixtures/irc-channels.sourcehut-parallel b/fixtures/irc-channels.sourcehut-parallel deleted file mode 100644 index 2c8e4ac3..00000000 --- a/fixtures/irc-channels.sourcehut-parallel +++ /dev/null @@ -1,1552 +0,0 @@ -# SUCCESS -# *INFO* Generating Sourcehut config for testing for GHC versions: 7.8.1 7.8.2 7.8.3 7.8.4 7.10.1 7.10.2 7.10.3 8.0.1 8.0.2 8.2.1 8.2.2 8.4.1 8.4.2 8.4.3 8.4.4 8.6.1 8.6.2 8.6.3 8.6.4 8.6.5 8.8.1 8.8.2 8.8.3 8.8.4 8.10.1 8.10.2 8.10.3 8.10.4 8.10.5 8.10.6 8.10.7 -# manifest name: 7.10.1 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--irc-channels=irc.libera.chat#mychannel' 'sourcehut' 'irc-channels.project' -# -# 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 -# -# REGENDATA ["--irc-channels=irc.libera.chat#mychannel","sourcehut","irc-channels.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-7.10.1 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 7_10_1-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.10.1 - - 7_10_1-check: | - cd example.org - cabal check - - 7_10_1-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 7_10_1-build: | - cd example.org - cabal build all - - 7_10_1-test: | - cd example.org - cabal test all --enable-tests - - 7_10_1-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 7.10.2 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--irc-channels=irc.libera.chat#mychannel' 'sourcehut' 'irc-channels.project' -# -# 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 -# -# REGENDATA ["--irc-channels=irc.libera.chat#mychannel","sourcehut","irc-channels.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-7.10.2 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 7_10_2-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.10.2 - - 7_10_2-check: | - cd example.org - cabal check - - 7_10_2-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 7_10_2-build: | - cd example.org - cabal build all - - 7_10_2-test: | - cd example.org - cabal test all --enable-tests - - 7_10_2-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 7.10.3 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--irc-channels=irc.libera.chat#mychannel' 'sourcehut' 'irc-channels.project' -# -# 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 -# -# REGENDATA ["--irc-channels=irc.libera.chat#mychannel","sourcehut","irc-channels.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-7.10.3 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 7_10_3-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.10.3 - - 7_10_3-check: | - cd example.org - cabal check - - 7_10_3-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 7_10_3-build: | - cd example.org - cabal build all - - 7_10_3-test: | - cd example.org - cabal test all --enable-tests - - 7_10_3-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 7.8.1 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--irc-channels=irc.libera.chat#mychannel' 'sourcehut' 'irc-channels.project' -# -# 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 -# -# REGENDATA ["--irc-channels=irc.libera.chat#mychannel","sourcehut","irc-channels.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-7.8.1 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 7_8_1-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.8.1 - - 7_8_1-check: | - cd example.org - cabal check - - 7_8_1-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 7_8_1-build: | - cd example.org - cabal build all - - 7_8_1-test: | - cd example.org - cabal test all --enable-tests - - 7_8_1-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 7.8.2 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--irc-channels=irc.libera.chat#mychannel' 'sourcehut' 'irc-channels.project' -# -# 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 -# -# REGENDATA ["--irc-channels=irc.libera.chat#mychannel","sourcehut","irc-channels.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-7.8.2 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 7_8_2-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.8.2 - - 7_8_2-check: | - cd example.org - cabal check - - 7_8_2-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 7_8_2-build: | - cd example.org - cabal build all - - 7_8_2-test: | - cd example.org - cabal test all --enable-tests - - 7_8_2-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 7.8.3 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--irc-channels=irc.libera.chat#mychannel' 'sourcehut' 'irc-channels.project' -# -# 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 -# -# REGENDATA ["--irc-channels=irc.libera.chat#mychannel","sourcehut","irc-channels.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-7.8.3 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 7_8_3-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.8.3 - - 7_8_3-check: | - cd example.org - cabal check - - 7_8_3-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 7_8_3-build: | - cd example.org - cabal build all - - 7_8_3-test: | - cd example.org - cabal test all --enable-tests - - 7_8_3-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 7.8.4 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--irc-channels=irc.libera.chat#mychannel' 'sourcehut' 'irc-channels.project' -# -# 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 -# -# REGENDATA ["--irc-channels=irc.libera.chat#mychannel","sourcehut","irc-channels.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-7.8.4 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 7_8_4-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.8.4 - - 7_8_4-check: | - cd example.org - cabal check - - 7_8_4-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 7_8_4-build: | - cd example.org - cabal build all - - 7_8_4-test: | - cd example.org - cabal test all --enable-tests - - 7_8_4-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.0.1 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--irc-channels=irc.libera.chat#mychannel' 'sourcehut' 'irc-channels.project' -# -# 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 -# -# REGENDATA ["--irc-channels=irc.libera.chat#mychannel","sourcehut","irc-channels.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.0.1 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_0_1-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.0.1 - - 8_0_1-check: | - cd example.org - cabal check - - 8_0_1-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_0_1-build: | - cd example.org - cabal build all - - 8_0_1-test: | - cd example.org - cabal test all --enable-tests - - 8_0_1-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.0.2 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--irc-channels=irc.libera.chat#mychannel' 'sourcehut' 'irc-channels.project' -# -# 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 -# -# REGENDATA ["--irc-channels=irc.libera.chat#mychannel","sourcehut","irc-channels.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.0.2 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_0_2-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.0.2 - - 8_0_2-check: | - cd example.org - cabal check - - 8_0_2-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_0_2-build: | - cd example.org - cabal build all - - 8_0_2-test: | - cd example.org - cabal test all --enable-tests - - 8_0_2-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.10.1 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--irc-channels=irc.libera.chat#mychannel' 'sourcehut' 'irc-channels.project' -# -# 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 -# -# REGENDATA ["--irc-channels=irc.libera.chat#mychannel","sourcehut","irc-channels.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.10.1 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_10_1-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.1 - - 8_10_1-check: | - cd example.org - cabal check - - 8_10_1-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_10_1-build: | - cd example.org - cabal build all - - 8_10_1-test: | - cd example.org - cabal test all --enable-tests - - 8_10_1-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.10.2 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--irc-channels=irc.libera.chat#mychannel' 'sourcehut' 'irc-channels.project' -# -# 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 -# -# REGENDATA ["--irc-channels=irc.libera.chat#mychannel","sourcehut","irc-channels.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.10.2 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_10_2-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.2 - - 8_10_2-check: | - cd example.org - cabal check - - 8_10_2-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_10_2-build: | - cd example.org - cabal build all - - 8_10_2-test: | - cd example.org - cabal test all --enable-tests - - 8_10_2-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.10.3 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--irc-channels=irc.libera.chat#mychannel' 'sourcehut' 'irc-channels.project' -# -# 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 -# -# REGENDATA ["--irc-channels=irc.libera.chat#mychannel","sourcehut","irc-channels.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.10.3 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_10_3-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.3 - - 8_10_3-check: | - cd example.org - cabal check - - 8_10_3-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_10_3-build: | - cd example.org - cabal build all - - 8_10_3-test: | - cd example.org - cabal test all --enable-tests - - 8_10_3-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.10.4 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--irc-channels=irc.libera.chat#mychannel' 'sourcehut' 'irc-channels.project' -# -# 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 -# -# REGENDATA ["--irc-channels=irc.libera.chat#mychannel","sourcehut","irc-channels.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.10.4 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_10_4-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.4 - - 8_10_4-check: | - cd example.org - cabal check - - 8_10_4-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_10_4-build: | - cd example.org - cabal build all - - 8_10_4-test: | - cd example.org - cabal test all --enable-tests - - 8_10_4-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.10.5 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--irc-channels=irc.libera.chat#mychannel' 'sourcehut' 'irc-channels.project' -# -# 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 -# -# REGENDATA ["--irc-channels=irc.libera.chat#mychannel","sourcehut","irc-channels.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.10.5 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_10_5-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.5 - - 8_10_5-check: | - cd example.org - cabal check - - 8_10_5-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_10_5-build: | - cd example.org - cabal build all - - 8_10_5-test: | - cd example.org - cabal test all --enable-tests - - 8_10_5-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.10.6 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--irc-channels=irc.libera.chat#mychannel' 'sourcehut' 'irc-channels.project' -# -# 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 -# -# REGENDATA ["--irc-channels=irc.libera.chat#mychannel","sourcehut","irc-channels.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.10.6 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_10_6-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.6 - - 8_10_6-check: | - cd example.org - cabal check - - 8_10_6-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_10_6-build: | - cd example.org - cabal build all - - 8_10_6-test: | - cd example.org - cabal test all --enable-tests - - 8_10_6-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.10.7 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--irc-channels=irc.libera.chat#mychannel' 'sourcehut' 'irc-channels.project' -# -# 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 -# -# REGENDATA ["--irc-channels=irc.libera.chat#mychannel","sourcehut","irc-channels.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.10.7 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_10_7-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.7 - - 8_10_7-check: | - cd example.org - cabal check - - 8_10_7-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_10_7-build: | - cd example.org - cabal build all - - 8_10_7-test: | - cd example.org - cabal test all --enable-tests - - 8_10_7-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.2.1 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--irc-channels=irc.libera.chat#mychannel' 'sourcehut' 'irc-channels.project' -# -# 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 -# -# REGENDATA ["--irc-channels=irc.libera.chat#mychannel","sourcehut","irc-channels.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.2.1 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_2_1-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.2.1 - - 8_2_1-check: | - cd example.org - cabal check - - 8_2_1-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_2_1-build: | - cd example.org - cabal build all - - 8_2_1-test: | - cd example.org - cabal test all --enable-tests - - 8_2_1-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.2.2 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--irc-channels=irc.libera.chat#mychannel' 'sourcehut' 'irc-channels.project' -# -# 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 -# -# REGENDATA ["--irc-channels=irc.libera.chat#mychannel","sourcehut","irc-channels.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.2.2 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_2_2-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.2.2 - - 8_2_2-check: | - cd example.org - cabal check - - 8_2_2-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_2_2-build: | - cd example.org - cabal build all - - 8_2_2-test: | - cd example.org - cabal test all --enable-tests - - 8_2_2-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.4.1 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--irc-channels=irc.libera.chat#mychannel' 'sourcehut' 'irc-channels.project' -# -# 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 -# -# REGENDATA ["--irc-channels=irc.libera.chat#mychannel","sourcehut","irc-channels.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.4.1 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_4_1-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.4.1 - - 8_4_1-check: | - cd example.org - cabal check - - 8_4_1-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_4_1-build: | - cd example.org - cabal build all - - 8_4_1-test: | - cd example.org - cabal test all --enable-tests - - 8_4_1-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.4.2 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--irc-channels=irc.libera.chat#mychannel' 'sourcehut' 'irc-channels.project' -# -# 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 -# -# REGENDATA ["--irc-channels=irc.libera.chat#mychannel","sourcehut","irc-channels.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.4.2 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_4_2-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.4.2 - - 8_4_2-check: | - cd example.org - cabal check - - 8_4_2-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_4_2-build: | - cd example.org - cabal build all - - 8_4_2-test: | - cd example.org - cabal test all --enable-tests - - 8_4_2-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.4.3 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--irc-channels=irc.libera.chat#mychannel' 'sourcehut' 'irc-channels.project' -# -# 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 -# -# REGENDATA ["--irc-channels=irc.libera.chat#mychannel","sourcehut","irc-channels.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.4.3 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_4_3-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.4.3 - - 8_4_3-check: | - cd example.org - cabal check - - 8_4_3-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_4_3-build: | - cd example.org - cabal build all - - 8_4_3-test: | - cd example.org - cabal test all --enable-tests - - 8_4_3-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.4.4 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--irc-channels=irc.libera.chat#mychannel' 'sourcehut' 'irc-channels.project' -# -# 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 -# -# REGENDATA ["--irc-channels=irc.libera.chat#mychannel","sourcehut","irc-channels.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.4.4 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_4_4-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.4.4 - - 8_4_4-check: | - cd example.org - cabal check - - 8_4_4-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_4_4-build: | - cd example.org - cabal build all - - 8_4_4-test: | - cd example.org - cabal test all --enable-tests - - 8_4_4-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.6.1 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--irc-channels=irc.libera.chat#mychannel' 'sourcehut' 'irc-channels.project' -# -# 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 -# -# REGENDATA ["--irc-channels=irc.libera.chat#mychannel","sourcehut","irc-channels.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.6.1 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_6_1-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.6.1 - - 8_6_1-check: | - cd example.org - cabal check - - 8_6_1-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_6_1-build: | - cd example.org - cabal build all - - 8_6_1-test: | - cd example.org - cabal test all --enable-tests - - 8_6_1-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.6.2 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--irc-channels=irc.libera.chat#mychannel' 'sourcehut' 'irc-channels.project' -# -# 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 -# -# REGENDATA ["--irc-channels=irc.libera.chat#mychannel","sourcehut","irc-channels.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.6.2 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_6_2-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.6.2 - - 8_6_2-check: | - cd example.org - cabal check - - 8_6_2-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_6_2-build: | - cd example.org - cabal build all - - 8_6_2-test: | - cd example.org - cabal test all --enable-tests - - 8_6_2-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.6.3 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--irc-channels=irc.libera.chat#mychannel' 'sourcehut' 'irc-channels.project' -# -# 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 -# -# REGENDATA ["--irc-channels=irc.libera.chat#mychannel","sourcehut","irc-channels.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.6.3 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_6_3-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.6.3 - - 8_6_3-check: | - cd example.org - cabal check - - 8_6_3-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_6_3-build: | - cd example.org - cabal build all - - 8_6_3-test: | - cd example.org - cabal test all --enable-tests - - 8_6_3-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.6.4 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--irc-channels=irc.libera.chat#mychannel' 'sourcehut' 'irc-channels.project' -# -# 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 -# -# REGENDATA ["--irc-channels=irc.libera.chat#mychannel","sourcehut","irc-channels.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.6.4 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_6_4-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.6.4 - - 8_6_4-check: | - cd example.org - cabal check - - 8_6_4-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_6_4-build: | - cd example.org - cabal build all - - 8_6_4-test: | - cd example.org - cabal test all --enable-tests - - 8_6_4-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.6.5 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--irc-channels=irc.libera.chat#mychannel' 'sourcehut' 'irc-channels.project' -# -# 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 -# -# REGENDATA ["--irc-channels=irc.libera.chat#mychannel","sourcehut","irc-channels.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.6.5 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_6_5-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.6.5 - - 8_6_5-check: | - cd example.org - cabal check - - 8_6_5-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_6_5-build: | - cd example.org - cabal build all - - 8_6_5-test: | - cd example.org - cabal test all --enable-tests - - 8_6_5-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.8.1 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--irc-channels=irc.libera.chat#mychannel' 'sourcehut' 'irc-channels.project' -# -# 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 -# -# REGENDATA ["--irc-channels=irc.libera.chat#mychannel","sourcehut","irc-channels.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.8.1 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_8_1-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.8.1 - - 8_8_1-check: | - cd example.org - cabal check - - 8_8_1-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_8_1-build: | - cd example.org - cabal build all - - 8_8_1-test: | - cd example.org - cabal test all --enable-tests - - 8_8_1-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.8.2 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--irc-channels=irc.libera.chat#mychannel' 'sourcehut' 'irc-channels.project' -# -# 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 -# -# REGENDATA ["--irc-channels=irc.libera.chat#mychannel","sourcehut","irc-channels.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.8.2 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_8_2-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.8.2 - - 8_8_2-check: | - cd example.org - cabal check - - 8_8_2-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_8_2-build: | - cd example.org - cabal build all - - 8_8_2-test: | - cd example.org - cabal test all --enable-tests - - 8_8_2-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.8.3 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--irc-channels=irc.libera.chat#mychannel' 'sourcehut' 'irc-channels.project' -# -# 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 -# -# REGENDATA ["--irc-channels=irc.libera.chat#mychannel","sourcehut","irc-channels.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.8.3 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_8_3-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.8.3 - - 8_8_3-check: | - cd example.org - cabal check - - 8_8_3-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_8_3-build: | - cd example.org - cabal build all - - 8_8_3-test: | - cd example.org - cabal test all --enable-tests - - 8_8_3-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.8.4 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--irc-channels=irc.libera.chat#mychannel' 'sourcehut' 'irc-channels.project' -# -# 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 -# -# REGENDATA ["--irc-channels=irc.libera.chat#mychannel","sourcehut","irc-channels.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.8.4 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_8_4-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.8.4 - - 8_8_4-check: | - cd example.org - cabal check - - 8_8_4-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_8_4-build: | - cd example.org - cabal build all - - 8_8_4-test: | - cd example.org - cabal test all --enable-tests - - 8_8_4-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com diff --git a/fixtures/irc-channels.travis b/fixtures/irc-channels.travis index ca9a52ff..d5c5ee0a 100644 --- a/fixtures/irc-channels.travis +++ b/fixtures/irc-channels.travis @@ -2,7 +2,7 @@ # *INFO* Generating Travis-CI config for testing for GHC versions: 7.8.1 7.8.2 7.8.3 7.8.4 7.10.1 7.10.2 7.10.3 8.0.1 8.0.2 8.2.1 8.2.2 8.4.1 8.4.2 8.4.3 8.4.4 8.6.1 8.6.2 8.6.3 8.6.4 8.6.5 8.8.1 8.8.2 8.8.3 8.8.4 8.10.1 8.10.2 8.10.3 8.10.4 8.10.5 8.10.6 8.10.7 # This Travis job script has been generated by a script via # -# haskell-ci '--irc-channels=irc.libera.chat#mychannel' 'travis' 'irc-channels.project' +# haskell-ci '--irc-channels=irc.libera.chat#mychannel' 'travis' 'irc-channels.project' '--sourcehut-source' 'https://example.org' # # To regenerate the script (for example after adjusting tested-with) run # @@ -230,5 +230,5 @@ script: - rm -f cabal.project.local - ${CABAL} v2-build $WITHCOMPILER --disable-tests --disable-benchmarks all -# REGENDATA ["--irc-channels=irc.libera.chat#mychannel","travis","irc-channels.project"] +# REGENDATA ["--irc-channels=irc.libera.chat#mychannel","travis","irc-channels.project","--sourcehut-source","https://example.org"] # EOF diff --git a/fixtures/messy.bash b/fixtures/messy.bash index f27e082c..39032459 100644 --- a/fixtures/messy.bash +++ b/fixtures/messy.bash @@ -2,7 +2,7 @@ # *INFO* Generating Bash script for testing for GHC versions: ghc-head 7.8.1 7.8.2 7.8.3 7.8.4 7.10.1 7.10.2 7.10.3 8.0.1 8.0.2 8.2.1 8.2.2 8.4.1 8.4.2 8.4.3 8.4.4 8.6.1 8.6.2 8.6.3 8.6.4 8.6.5 8.8.1 8.8.2 8.8.3 8.8.4 8.10.1 8.10.2 8.10.3 8.10.4 8.10.5 8.10.6 8.10.7 #!/bin/bash # shellcheck disable=SC2086,SC2016,SC2046 -# REGENDATA ["--ghc-head","--apt=fftw3-dev","--installed=-all +deepseq","bash","messy.project"] +# REGENDATA ["--ghc-head","--apt=fftw3-dev","--installed=-all +deepseq","bash","messy.project","--sourcehut-source","https://example.org"] set -o pipefail diff --git a/fixtures/messy.github b/fixtures/messy.github index 93be6624..8c34abe6 100644 --- a/fixtures/messy.github +++ b/fixtures/messy.github @@ -2,7 +2,7 @@ # *INFO* Generating GitHub config for testing for GHC versions: ghc-head 7.8.1 7.8.2 7.8.3 7.8.4 7.10.1 7.10.2 7.10.3 8.0.1 8.0.2 8.2.1 8.2.2 8.4.1 8.4.2 8.4.3 8.4.4 8.6.1 8.6.2 8.6.3 8.6.4 8.6.5 8.8.1 8.8.2 8.8.3 8.8.4 8.10.1 8.10.2 8.10.3 8.10.4 8.10.5 8.10.6 8.10.7 # This GitHub workflow config has been generated by a script via # -# haskell-ci '--ghc-head' '--apt=fftw3-dev' '--installed=-all +deepseq' 'github' 'messy.project' +# haskell-ci '--ghc-head' '--apt=fftw3-dev' '--installed=-all +deepseq' 'github' 'messy.project' '--sourcehut-source' 'https://example.org' # # To regenerate the script (for example after adjusting tested-with) run # @@ -10,7 +10,7 @@ # # For more information, see https://github.com/haskell-CI/haskell-ci # -# REGENDATA ["--ghc-head","--apt=fftw3-dev","--installed=-all +deepseq","github","messy.project"] +# REGENDATA ["--ghc-head","--apt=fftw3-dev","--installed=-all +deepseq","github","messy.project","--sourcehut-source","https://example.org"] # name: Haskell-CI on: diff --git a/fixtures/messy.sourcehut b/fixtures/messy.sourcehut index b5414979..e4359340 100644 --- a/fixtures/messy.sourcehut +++ b/fixtures/messy.sourcehut @@ -3,7 +3,7 @@ # manifest name: all # This Sourcehut job script has been generated by a script via # -# haskell-ci '--ghc-head' '--apt=fftw3-dev' '--installed=-all +deepseq' 'sourcehut' 'messy.project' +# haskell-ci '--ghc-head' '--apt=fftw3-dev' '--installed=-all +deepseq' 'sourcehut' 'messy.project' '--sourcehut-source' 'https://example.org' # # To regenerate the script (for example after adjusting tested-with) run # @@ -11,7 +11,7 @@ # # For more information, see https://github.com/haskell-CI/haskell-ci # -# REGENDATA ["--ghc-head","--apt=fftw3-dev","--installed=-all +deepseq","sourcehut","messy.project"] +# REGENDATA ["--ghc-head","--apt=fftw3-dev","--installed=-all +deepseq","sourcehut","messy.project","--sourcehut-source","https://example.org"] # image: ubuntu/bionic packages: diff --git a/fixtures/messy.sourcehut-parallel b/fixtures/messy.sourcehut-parallel deleted file mode 100644 index bfdfe8ac..00000000 --- a/fixtures/messy.sourcehut-parallel +++ /dev/null @@ -1,1634 +0,0 @@ -# SUCCESS -# *INFO* Generating Sourcehut config for testing for GHC versions: ghc-head 7.8.1 7.8.2 7.8.3 7.8.4 7.10.1 7.10.2 7.10.3 8.0.1 8.0.2 8.2.1 8.2.2 8.4.1 8.4.2 8.4.3 8.4.4 8.6.1 8.6.2 8.6.3 8.6.4 8.6.5 8.8.1 8.8.2 8.8.3 8.8.4 8.10.1 8.10.2 8.10.3 8.10.4 8.10.5 8.10.6 8.10.7 -# manifest name: 7.10.1 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--ghc-head' '--apt=fftw3-dev' '--installed=-all +deepseq' 'sourcehut' 'messy.project' -# -# 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 -# -# REGENDATA ["--ghc-head","--apt=fftw3-dev","--installed=-all +deepseq","sourcehut","messy.project"] -# -image: ubuntu/bionic -packages: - - fftw3-dev - - gcc - - cabal-install-3.4 - - ghc-7.10.1 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 7_10_1-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.10.1 - - 7_10_1-check: | - cd example.org - cabal check - - 7_10_1-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 7_10_1-build: | - cd example.org - cabal build all - - 7_10_1-test: | - cd example.org - cabal test all --enable-tests - - 7_10_1-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 7.10.2 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--ghc-head' '--apt=fftw3-dev' '--installed=-all +deepseq' 'sourcehut' 'messy.project' -# -# 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 -# -# REGENDATA ["--ghc-head","--apt=fftw3-dev","--installed=-all +deepseq","sourcehut","messy.project"] -# -image: ubuntu/bionic -packages: - - fftw3-dev - - gcc - - cabal-install-3.4 - - ghc-7.10.2 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 7_10_2-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.10.2 - - 7_10_2-check: | - cd example.org - cabal check - - 7_10_2-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 7_10_2-build: | - cd example.org - cabal build all - - 7_10_2-test: | - cd example.org - cabal test all --enable-tests - - 7_10_2-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 7.10.3 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--ghc-head' '--apt=fftw3-dev' '--installed=-all +deepseq' 'sourcehut' 'messy.project' -# -# 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 -# -# REGENDATA ["--ghc-head","--apt=fftw3-dev","--installed=-all +deepseq","sourcehut","messy.project"] -# -image: ubuntu/bionic -packages: - - fftw3-dev - - gcc - - cabal-install-3.4 - - ghc-7.10.3 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 7_10_3-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.10.3 - - 7_10_3-check: | - cd example.org - cabal check - - 7_10_3-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 7_10_3-build: | - cd example.org - cabal build all - - 7_10_3-test: | - cd example.org - cabal test all --enable-tests - - 7_10_3-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 7.8.1 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--ghc-head' '--apt=fftw3-dev' '--installed=-all +deepseq' 'sourcehut' 'messy.project' -# -# 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 -# -# REGENDATA ["--ghc-head","--apt=fftw3-dev","--installed=-all +deepseq","sourcehut","messy.project"] -# -image: ubuntu/bionic -packages: - - fftw3-dev - - gcc - - cabal-install-3.4 - - ghc-7.8.1 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 7_8_1-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.8.1 - - 7_8_1-check: | - cd example.org - cabal check - - 7_8_1-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 7_8_1-build: | - cd example.org - cabal build all - - 7_8_1-test: | - cd example.org - cabal test all --enable-tests - - 7_8_1-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 7.8.2 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--ghc-head' '--apt=fftw3-dev' '--installed=-all +deepseq' 'sourcehut' 'messy.project' -# -# 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 -# -# REGENDATA ["--ghc-head","--apt=fftw3-dev","--installed=-all +deepseq","sourcehut","messy.project"] -# -image: ubuntu/bionic -packages: - - fftw3-dev - - gcc - - cabal-install-3.4 - - ghc-7.8.2 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 7_8_2-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.8.2 - - 7_8_2-check: | - cd example.org - cabal check - - 7_8_2-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 7_8_2-build: | - cd example.org - cabal build all - - 7_8_2-test: | - cd example.org - cabal test all --enable-tests - - 7_8_2-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 7.8.3 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--ghc-head' '--apt=fftw3-dev' '--installed=-all +deepseq' 'sourcehut' 'messy.project' -# -# 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 -# -# REGENDATA ["--ghc-head","--apt=fftw3-dev","--installed=-all +deepseq","sourcehut","messy.project"] -# -image: ubuntu/bionic -packages: - - fftw3-dev - - gcc - - cabal-install-3.4 - - ghc-7.8.3 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 7_8_3-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.8.3 - - 7_8_3-check: | - cd example.org - cabal check - - 7_8_3-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 7_8_3-build: | - cd example.org - cabal build all - - 7_8_3-test: | - cd example.org - cabal test all --enable-tests - - 7_8_3-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 7.8.4 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--ghc-head' '--apt=fftw3-dev' '--installed=-all +deepseq' 'sourcehut' 'messy.project' -# -# 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 -# -# REGENDATA ["--ghc-head","--apt=fftw3-dev","--installed=-all +deepseq","sourcehut","messy.project"] -# -image: ubuntu/bionic -packages: - - fftw3-dev - - gcc - - cabal-install-3.4 - - ghc-7.8.4 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 7_8_4-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.8.4 - - 7_8_4-check: | - cd example.org - cabal check - - 7_8_4-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 7_8_4-build: | - cd example.org - cabal build all - - 7_8_4-test: | - cd example.org - cabal test all --enable-tests - - 7_8_4-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.0.1 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--ghc-head' '--apt=fftw3-dev' '--installed=-all +deepseq' 'sourcehut' 'messy.project' -# -# 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 -# -# REGENDATA ["--ghc-head","--apt=fftw3-dev","--installed=-all +deepseq","sourcehut","messy.project"] -# -image: ubuntu/bionic -packages: - - fftw3-dev - - gcc - - cabal-install-3.4 - - ghc-8.0.1 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_0_1-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.0.1 - - 8_0_1-check: | - cd example.org - cabal check - - 8_0_1-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_0_1-build: | - cd example.org - cabal build all - - 8_0_1-test: | - cd example.org - cabal test all --enable-tests - - 8_0_1-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.0.2 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--ghc-head' '--apt=fftw3-dev' '--installed=-all +deepseq' 'sourcehut' 'messy.project' -# -# 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 -# -# REGENDATA ["--ghc-head","--apt=fftw3-dev","--installed=-all +deepseq","sourcehut","messy.project"] -# -image: ubuntu/bionic -packages: - - fftw3-dev - - gcc - - cabal-install-3.4 - - ghc-8.0.2 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_0_2-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.0.2 - - 8_0_2-check: | - cd example.org - cabal check - - 8_0_2-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_0_2-build: | - cd example.org - cabal build all - - 8_0_2-test: | - cd example.org - cabal test all --enable-tests - - 8_0_2-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.10.1 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--ghc-head' '--apt=fftw3-dev' '--installed=-all +deepseq' 'sourcehut' 'messy.project' -# -# 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 -# -# REGENDATA ["--ghc-head","--apt=fftw3-dev","--installed=-all +deepseq","sourcehut","messy.project"] -# -image: ubuntu/bionic -packages: - - fftw3-dev - - gcc - - cabal-install-3.4 - - ghc-8.10.1 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_10_1-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.1 - - 8_10_1-check: | - cd example.org - cabal check - - 8_10_1-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_10_1-build: | - cd example.org - cabal build all - - 8_10_1-test: | - cd example.org - cabal test all --enable-tests - - 8_10_1-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.10.2 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--ghc-head' '--apt=fftw3-dev' '--installed=-all +deepseq' 'sourcehut' 'messy.project' -# -# 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 -# -# REGENDATA ["--ghc-head","--apt=fftw3-dev","--installed=-all +deepseq","sourcehut","messy.project"] -# -image: ubuntu/bionic -packages: - - fftw3-dev - - gcc - - cabal-install-3.4 - - ghc-8.10.2 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_10_2-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.2 - - 8_10_2-check: | - cd example.org - cabal check - - 8_10_2-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_10_2-build: | - cd example.org - cabal build all - - 8_10_2-test: | - cd example.org - cabal test all --enable-tests - - 8_10_2-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.10.3 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--ghc-head' '--apt=fftw3-dev' '--installed=-all +deepseq' 'sourcehut' 'messy.project' -# -# 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 -# -# REGENDATA ["--ghc-head","--apt=fftw3-dev","--installed=-all +deepseq","sourcehut","messy.project"] -# -image: ubuntu/bionic -packages: - - fftw3-dev - - gcc - - cabal-install-3.4 - - ghc-8.10.3 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_10_3-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.3 - - 8_10_3-check: | - cd example.org - cabal check - - 8_10_3-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_10_3-build: | - cd example.org - cabal build all - - 8_10_3-test: | - cd example.org - cabal test all --enable-tests - - 8_10_3-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.10.4 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--ghc-head' '--apt=fftw3-dev' '--installed=-all +deepseq' 'sourcehut' 'messy.project' -# -# 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 -# -# REGENDATA ["--ghc-head","--apt=fftw3-dev","--installed=-all +deepseq","sourcehut","messy.project"] -# -image: ubuntu/bionic -packages: - - fftw3-dev - - gcc - - cabal-install-3.4 - - ghc-8.10.4 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_10_4-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.4 - - 8_10_4-check: | - cd example.org - cabal check - - 8_10_4-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_10_4-build: | - cd example.org - cabal build all - - 8_10_4-test: | - cd example.org - cabal test all --enable-tests - - 8_10_4-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.10.5 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--ghc-head' '--apt=fftw3-dev' '--installed=-all +deepseq' 'sourcehut' 'messy.project' -# -# 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 -# -# REGENDATA ["--ghc-head","--apt=fftw3-dev","--installed=-all +deepseq","sourcehut","messy.project"] -# -image: ubuntu/bionic -packages: - - fftw3-dev - - gcc - - cabal-install-3.4 - - ghc-8.10.5 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_10_5-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.5 - - 8_10_5-check: | - cd example.org - cabal check - - 8_10_5-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_10_5-build: | - cd example.org - cabal build all - - 8_10_5-test: | - cd example.org - cabal test all --enable-tests - - 8_10_5-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.10.6 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--ghc-head' '--apt=fftw3-dev' '--installed=-all +deepseq' 'sourcehut' 'messy.project' -# -# 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 -# -# REGENDATA ["--ghc-head","--apt=fftw3-dev","--installed=-all +deepseq","sourcehut","messy.project"] -# -image: ubuntu/bionic -packages: - - fftw3-dev - - gcc - - cabal-install-3.4 - - ghc-8.10.6 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_10_6-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.6 - - 8_10_6-check: | - cd example.org - cabal check - - 8_10_6-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_10_6-build: | - cd example.org - cabal build all - - 8_10_6-test: | - cd example.org - cabal test all --enable-tests - - 8_10_6-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.10.7 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--ghc-head' '--apt=fftw3-dev' '--installed=-all +deepseq' 'sourcehut' 'messy.project' -# -# 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 -# -# REGENDATA ["--ghc-head","--apt=fftw3-dev","--installed=-all +deepseq","sourcehut","messy.project"] -# -image: ubuntu/bionic -packages: - - fftw3-dev - - gcc - - cabal-install-3.4 - - ghc-8.10.7 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_10_7-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.7 - - 8_10_7-check: | - cd example.org - cabal check - - 8_10_7-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_10_7-build: | - cd example.org - cabal build all - - 8_10_7-test: | - cd example.org - cabal test all --enable-tests - - 8_10_7-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.2.1 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--ghc-head' '--apt=fftw3-dev' '--installed=-all +deepseq' 'sourcehut' 'messy.project' -# -# 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 -# -# REGENDATA ["--ghc-head","--apt=fftw3-dev","--installed=-all +deepseq","sourcehut","messy.project"] -# -image: ubuntu/bionic -packages: - - fftw3-dev - - gcc - - cabal-install-3.4 - - ghc-8.2.1 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_2_1-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.2.1 - - 8_2_1-check: | - cd example.org - cabal check - - 8_2_1-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_2_1-build: | - cd example.org - cabal build all - - 8_2_1-test: | - cd example.org - cabal test all --enable-tests - - 8_2_1-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.2.2 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--ghc-head' '--apt=fftw3-dev' '--installed=-all +deepseq' 'sourcehut' 'messy.project' -# -# 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 -# -# REGENDATA ["--ghc-head","--apt=fftw3-dev","--installed=-all +deepseq","sourcehut","messy.project"] -# -image: ubuntu/bionic -packages: - - fftw3-dev - - gcc - - cabal-install-3.4 - - ghc-8.2.2 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_2_2-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.2.2 - - 8_2_2-check: | - cd example.org - cabal check - - 8_2_2-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_2_2-build: | - cd example.org - cabal build all - - 8_2_2-test: | - cd example.org - cabal test all --enable-tests - - 8_2_2-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.4.1 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--ghc-head' '--apt=fftw3-dev' '--installed=-all +deepseq' 'sourcehut' 'messy.project' -# -# 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 -# -# REGENDATA ["--ghc-head","--apt=fftw3-dev","--installed=-all +deepseq","sourcehut","messy.project"] -# -image: ubuntu/bionic -packages: - - fftw3-dev - - gcc - - cabal-install-3.4 - - ghc-8.4.1 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_4_1-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.4.1 - - 8_4_1-check: | - cd example.org - cabal check - - 8_4_1-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_4_1-build: | - cd example.org - cabal build all - - 8_4_1-test: | - cd example.org - cabal test all --enable-tests - - 8_4_1-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.4.2 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--ghc-head' '--apt=fftw3-dev' '--installed=-all +deepseq' 'sourcehut' 'messy.project' -# -# 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 -# -# REGENDATA ["--ghc-head","--apt=fftw3-dev","--installed=-all +deepseq","sourcehut","messy.project"] -# -image: ubuntu/bionic -packages: - - fftw3-dev - - gcc - - cabal-install-3.4 - - ghc-8.4.2 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_4_2-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.4.2 - - 8_4_2-check: | - cd example.org - cabal check - - 8_4_2-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_4_2-build: | - cd example.org - cabal build all - - 8_4_2-test: | - cd example.org - cabal test all --enable-tests - - 8_4_2-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.4.3 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--ghc-head' '--apt=fftw3-dev' '--installed=-all +deepseq' 'sourcehut' 'messy.project' -# -# 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 -# -# REGENDATA ["--ghc-head","--apt=fftw3-dev","--installed=-all +deepseq","sourcehut","messy.project"] -# -image: ubuntu/bionic -packages: - - fftw3-dev - - gcc - - cabal-install-3.4 - - ghc-8.4.3 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_4_3-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.4.3 - - 8_4_3-check: | - cd example.org - cabal check - - 8_4_3-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_4_3-build: | - cd example.org - cabal build all - - 8_4_3-test: | - cd example.org - cabal test all --enable-tests - - 8_4_3-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.4.4 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--ghc-head' '--apt=fftw3-dev' '--installed=-all +deepseq' 'sourcehut' 'messy.project' -# -# 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 -# -# REGENDATA ["--ghc-head","--apt=fftw3-dev","--installed=-all +deepseq","sourcehut","messy.project"] -# -image: ubuntu/bionic -packages: - - fftw3-dev - - gcc - - cabal-install-3.4 - - ghc-8.4.4 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_4_4-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.4.4 - - 8_4_4-check: | - cd example.org - cabal check - - 8_4_4-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_4_4-build: | - cd example.org - cabal build all - - 8_4_4-test: | - cd example.org - cabal test all --enable-tests - - 8_4_4-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.6.1 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--ghc-head' '--apt=fftw3-dev' '--installed=-all +deepseq' 'sourcehut' 'messy.project' -# -# 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 -# -# REGENDATA ["--ghc-head","--apt=fftw3-dev","--installed=-all +deepseq","sourcehut","messy.project"] -# -image: ubuntu/bionic -packages: - - fftw3-dev - - gcc - - cabal-install-3.4 - - ghc-8.6.1 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_6_1-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.6.1 - - 8_6_1-check: | - cd example.org - cabal check - - 8_6_1-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_6_1-build: | - cd example.org - cabal build all - - 8_6_1-test: | - cd example.org - cabal test all --enable-tests - - 8_6_1-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.6.2 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--ghc-head' '--apt=fftw3-dev' '--installed=-all +deepseq' 'sourcehut' 'messy.project' -# -# 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 -# -# REGENDATA ["--ghc-head","--apt=fftw3-dev","--installed=-all +deepseq","sourcehut","messy.project"] -# -image: ubuntu/bionic -packages: - - fftw3-dev - - gcc - - cabal-install-3.4 - - ghc-8.6.2 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_6_2-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.6.2 - - 8_6_2-check: | - cd example.org - cabal check - - 8_6_2-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_6_2-build: | - cd example.org - cabal build all - - 8_6_2-test: | - cd example.org - cabal test all --enable-tests - - 8_6_2-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.6.3 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--ghc-head' '--apt=fftw3-dev' '--installed=-all +deepseq' 'sourcehut' 'messy.project' -# -# 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 -# -# REGENDATA ["--ghc-head","--apt=fftw3-dev","--installed=-all +deepseq","sourcehut","messy.project"] -# -image: ubuntu/bionic -packages: - - fftw3-dev - - gcc - - cabal-install-3.4 - - ghc-8.6.3 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_6_3-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.6.3 - - 8_6_3-check: | - cd example.org - cabal check - - 8_6_3-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_6_3-build: | - cd example.org - cabal build all - - 8_6_3-test: | - cd example.org - cabal test all --enable-tests - - 8_6_3-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.6.4 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--ghc-head' '--apt=fftw3-dev' '--installed=-all +deepseq' 'sourcehut' 'messy.project' -# -# 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 -# -# REGENDATA ["--ghc-head","--apt=fftw3-dev","--installed=-all +deepseq","sourcehut","messy.project"] -# -image: ubuntu/bionic -packages: - - fftw3-dev - - gcc - - cabal-install-3.4 - - ghc-8.6.4 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_6_4-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.6.4 - - 8_6_4-check: | - cd example.org - cabal check - - 8_6_4-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_6_4-build: | - cd example.org - cabal build all - - 8_6_4-test: | - cd example.org - cabal test all --enable-tests - - 8_6_4-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.6.5 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--ghc-head' '--apt=fftw3-dev' '--installed=-all +deepseq' 'sourcehut' 'messy.project' -# -# 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 -# -# REGENDATA ["--ghc-head","--apt=fftw3-dev","--installed=-all +deepseq","sourcehut","messy.project"] -# -image: ubuntu/bionic -packages: - - fftw3-dev - - gcc - - cabal-install-3.4 - - ghc-8.6.5 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_6_5-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.6.5 - - 8_6_5-check: | - cd example.org - cabal check - - 8_6_5-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_6_5-build: | - cd example.org - cabal build all - - 8_6_5-test: | - cd example.org - cabal test all --enable-tests - - 8_6_5-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.8.1 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--ghc-head' '--apt=fftw3-dev' '--installed=-all +deepseq' 'sourcehut' 'messy.project' -# -# 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 -# -# REGENDATA ["--ghc-head","--apt=fftw3-dev","--installed=-all +deepseq","sourcehut","messy.project"] -# -image: ubuntu/bionic -packages: - - fftw3-dev - - gcc - - cabal-install-3.4 - - ghc-8.8.1 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_8_1-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.8.1 - - 8_8_1-check: | - cd example.org - cabal check - - 8_8_1-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_8_1-build: | - cd example.org - cabal build all - - 8_8_1-test: | - cd example.org - cabal test all --enable-tests - - 8_8_1-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.8.2 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--ghc-head' '--apt=fftw3-dev' '--installed=-all +deepseq' 'sourcehut' 'messy.project' -# -# 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 -# -# REGENDATA ["--ghc-head","--apt=fftw3-dev","--installed=-all +deepseq","sourcehut","messy.project"] -# -image: ubuntu/bionic -packages: - - fftw3-dev - - gcc - - cabal-install-3.4 - - ghc-8.8.2 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_8_2-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.8.2 - - 8_8_2-check: | - cd example.org - cabal check - - 8_8_2-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_8_2-build: | - cd example.org - cabal build all - - 8_8_2-test: | - cd example.org - cabal test all --enable-tests - - 8_8_2-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.8.3 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--ghc-head' '--apt=fftw3-dev' '--installed=-all +deepseq' 'sourcehut' 'messy.project' -# -# 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 -# -# REGENDATA ["--ghc-head","--apt=fftw3-dev","--installed=-all +deepseq","sourcehut","messy.project"] -# -image: ubuntu/bionic -packages: - - fftw3-dev - - gcc - - cabal-install-3.4 - - ghc-8.8.3 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_8_3-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.8.3 - - 8_8_3-check: | - cd example.org - cabal check - - 8_8_3-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_8_3-build: | - cd example.org - cabal build all - - 8_8_3-test: | - cd example.org - cabal test all --enable-tests - - 8_8_3-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.8.4 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--ghc-head' '--apt=fftw3-dev' '--installed=-all +deepseq' 'sourcehut' 'messy.project' -# -# 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 -# -# REGENDATA ["--ghc-head","--apt=fftw3-dev","--installed=-all +deepseq","sourcehut","messy.project"] -# -image: ubuntu/bionic -packages: - - fftw3-dev - - gcc - - cabal-install-3.4 - - ghc-8.8.4 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_8_4-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.8.4 - - 8_8_4-check: | - cd example.org - cabal check - - 8_8_4-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_8_4-build: | - cd example.org - cabal build all - - 8_8_4-test: | - cd example.org - cabal test all --enable-tests - - 8_8_4-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: ghc-head -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--ghc-head' '--apt=fftw3-dev' '--installed=-all +deepseq' 'sourcehut' 'messy.project' -# -# 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 -# -# REGENDATA ["--ghc-head","--apt=fftw3-dev","--installed=-all +deepseq","sourcehut","messy.project"] -# -image: ubuntu/bionic -packages: - - fftw3-dev - - gcc - - cabal-install-3.4 - - ghc-head -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - ghc-head-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-head - - ghc-head-check: | - cd example.org - cabal check - - ghc-head-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - ghc-head-build: | - cd example.org - cabal build all - - ghc-head-test: | - cd example.org - cabal test all --enable-tests - - ghc-head-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com diff --git a/fixtures/messy.travis b/fixtures/messy.travis index 31370e55..95aa78e0 100644 --- a/fixtures/messy.travis +++ b/fixtures/messy.travis @@ -2,7 +2,7 @@ # *INFO* Generating Travis-CI config for testing for GHC versions: ghc-head 7.8.1 7.8.2 7.8.3 7.8.4 7.10.1 7.10.2 7.10.3 8.0.1 8.0.2 8.2.1 8.2.2 8.4.1 8.4.2 8.4.3 8.4.4 8.6.1 8.6.2 8.6.3 8.6.4 8.6.5 8.8.1 8.8.2 8.8.3 8.8.4 8.10.1 8.10.2 8.10.3 8.10.4 8.10.5 8.10.6 8.10.7 # This Travis job script has been generated by a script via # -# haskell-ci '--ghc-head' '--apt=fftw3-dev' '--installed=-all +deepseq' 'travis' 'messy.project' +# haskell-ci '--ghc-head' '--apt=fftw3-dev' '--installed=-all +deepseq' 'travis' 'messy.project' '--sourcehut-source' 'https://example.org' # # To regenerate the script (for example after adjusting tested-with) run # @@ -275,5 +275,5 @@ script: - rm -f cabal.project.local - ${CABAL} v2-build $WITHCOMPILER --disable-tests --disable-benchmarks all -# REGENDATA ["--ghc-head","--apt=fftw3-dev","--installed=-all +deepseq","travis","messy.project"] +# REGENDATA ["--ghc-head","--apt=fftw3-dev","--installed=-all +deepseq","travis","messy.project","--sourcehut-source","https://example.org"] # EOF diff --git a/fixtures/psql.bash b/fixtures/psql.bash index a53ea8e1..602e8d3a 100644 --- a/fixtures/psql.bash +++ b/fixtures/psql.bash @@ -2,7 +2,7 @@ # *INFO* Generating Bash script for testing for GHC versions: 7.8.1 7.8.2 7.8.3 7.8.4 7.10.1 7.10.2 7.10.3 8.0.1 8.0.2 8.2.1 8.2.2 8.4.1 8.4.2 8.4.3 8.4.4 8.6.1 8.6.2 8.6.3 8.6.4 8.6.5 8.8.1 8.8.2 8.8.3 8.8.4 8.10.1 8.10.2 8.10.3 8.10.4 8.10.5 8.10.6 8.10.7 #!/bin/bash # shellcheck disable=SC2086,SC2016,SC2046 -# REGENDATA ["--postgresql","bash","psql.project"] +# REGENDATA ["--postgresql","bash","psql.project","--sourcehut-source","https://example.org"] set -o pipefail diff --git a/fixtures/psql.github b/fixtures/psql.github index 7f373ea5..800ecb67 100644 --- a/fixtures/psql.github +++ b/fixtures/psql.github @@ -2,7 +2,7 @@ # *INFO* Generating GitHub config for testing for GHC versions: 7.8.1 7.8.2 7.8.3 7.8.4 7.10.1 7.10.2 7.10.3 8.0.1 8.0.2 8.2.1 8.2.2 8.4.1 8.4.2 8.4.3 8.4.4 8.6.1 8.6.2 8.6.3 8.6.4 8.6.5 8.8.1 8.8.2 8.8.3 8.8.4 8.10.1 8.10.2 8.10.3 8.10.4 8.10.5 8.10.6 8.10.7 # This GitHub workflow config has been generated by a script via # -# haskell-ci '--postgresql' 'github' 'psql.project' +# haskell-ci '--postgresql' 'github' 'psql.project' '--sourcehut-source' 'https://example.org' # # To regenerate the script (for example after adjusting tested-with) run # @@ -10,7 +10,7 @@ # # For more information, see https://github.com/haskell-CI/haskell-ci # -# REGENDATA ["--postgresql","github","psql.project"] +# REGENDATA ["--postgresql","github","psql.project","--sourcehut-source","https://example.org"] # name: Haskell-CI on: diff --git a/fixtures/psql.sourcehut b/fixtures/psql.sourcehut index 630036c1..dd49bdef 100644 --- a/fixtures/psql.sourcehut +++ b/fixtures/psql.sourcehut @@ -3,7 +3,7 @@ # manifest name: all # This Sourcehut job script has been generated by a script via # -# haskell-ci '--postgresql' 'sourcehut' 'psql.project' +# haskell-ci '--postgresql' 'sourcehut' 'psql.project' '--sourcehut-source' 'https://example.org' # # To regenerate the script (for example after adjusting tested-with) run # @@ -11,7 +11,7 @@ # # For more information, see https://github.com/haskell-CI/haskell-ci # -# REGENDATA ["--postgresql","sourcehut","psql.project"] +# REGENDATA ["--postgresql","sourcehut","psql.project","--sourcehut-source","https://example.org"] # image: ubuntu/bionic packages: diff --git a/fixtures/psql.sourcehut-parallel b/fixtures/psql.sourcehut-parallel deleted file mode 100644 index cc5d5312..00000000 --- a/fixtures/psql.sourcehut-parallel +++ /dev/null @@ -1,1552 +0,0 @@ -# SUCCESS -# *INFO* Generating Sourcehut config for testing for GHC versions: 7.8.1 7.8.2 7.8.3 7.8.4 7.10.1 7.10.2 7.10.3 8.0.1 8.0.2 8.2.1 8.2.2 8.4.1 8.4.2 8.4.3 8.4.4 8.6.1 8.6.2 8.6.3 8.6.4 8.6.5 8.8.1 8.8.2 8.8.3 8.8.4 8.10.1 8.10.2 8.10.3 8.10.4 8.10.5 8.10.6 8.10.7 -# manifest name: 7.10.1 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--postgresql' 'sourcehut' 'psql.project' -# -# 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 -# -# REGENDATA ["--postgresql","sourcehut","psql.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-7.10.1 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 7_10_1-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.10.1 - - 7_10_1-check: | - cd example.org - cabal check - - 7_10_1-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 7_10_1-build: | - cd example.org - cabal build all - - 7_10_1-test: | - cd example.org - cabal test all --enable-tests - - 7_10_1-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 7.10.2 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--postgresql' 'sourcehut' 'psql.project' -# -# 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 -# -# REGENDATA ["--postgresql","sourcehut","psql.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-7.10.2 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 7_10_2-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.10.2 - - 7_10_2-check: | - cd example.org - cabal check - - 7_10_2-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 7_10_2-build: | - cd example.org - cabal build all - - 7_10_2-test: | - cd example.org - cabal test all --enable-tests - - 7_10_2-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 7.10.3 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--postgresql' 'sourcehut' 'psql.project' -# -# 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 -# -# REGENDATA ["--postgresql","sourcehut","psql.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-7.10.3 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 7_10_3-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.10.3 - - 7_10_3-check: | - cd example.org - cabal check - - 7_10_3-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 7_10_3-build: | - cd example.org - cabal build all - - 7_10_3-test: | - cd example.org - cabal test all --enable-tests - - 7_10_3-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 7.8.1 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--postgresql' 'sourcehut' 'psql.project' -# -# 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 -# -# REGENDATA ["--postgresql","sourcehut","psql.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-7.8.1 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 7_8_1-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.8.1 - - 7_8_1-check: | - cd example.org - cabal check - - 7_8_1-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 7_8_1-build: | - cd example.org - cabal build all - - 7_8_1-test: | - cd example.org - cabal test all --enable-tests - - 7_8_1-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 7.8.2 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--postgresql' 'sourcehut' 'psql.project' -# -# 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 -# -# REGENDATA ["--postgresql","sourcehut","psql.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-7.8.2 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 7_8_2-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.8.2 - - 7_8_2-check: | - cd example.org - cabal check - - 7_8_2-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 7_8_2-build: | - cd example.org - cabal build all - - 7_8_2-test: | - cd example.org - cabal test all --enable-tests - - 7_8_2-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 7.8.3 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--postgresql' 'sourcehut' 'psql.project' -# -# 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 -# -# REGENDATA ["--postgresql","sourcehut","psql.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-7.8.3 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 7_8_3-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.8.3 - - 7_8_3-check: | - cd example.org - cabal check - - 7_8_3-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 7_8_3-build: | - cd example.org - cabal build all - - 7_8_3-test: | - cd example.org - cabal test all --enable-tests - - 7_8_3-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 7.8.4 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--postgresql' 'sourcehut' 'psql.project' -# -# 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 -# -# REGENDATA ["--postgresql","sourcehut","psql.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-7.8.4 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 7_8_4-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.8.4 - - 7_8_4-check: | - cd example.org - cabal check - - 7_8_4-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 7_8_4-build: | - cd example.org - cabal build all - - 7_8_4-test: | - cd example.org - cabal test all --enable-tests - - 7_8_4-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.0.1 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--postgresql' 'sourcehut' 'psql.project' -# -# 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 -# -# REGENDATA ["--postgresql","sourcehut","psql.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.0.1 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_0_1-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.0.1 - - 8_0_1-check: | - cd example.org - cabal check - - 8_0_1-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_0_1-build: | - cd example.org - cabal build all - - 8_0_1-test: | - cd example.org - cabal test all --enable-tests - - 8_0_1-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.0.2 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--postgresql' 'sourcehut' 'psql.project' -# -# 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 -# -# REGENDATA ["--postgresql","sourcehut","psql.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.0.2 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_0_2-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.0.2 - - 8_0_2-check: | - cd example.org - cabal check - - 8_0_2-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_0_2-build: | - cd example.org - cabal build all - - 8_0_2-test: | - cd example.org - cabal test all --enable-tests - - 8_0_2-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.10.1 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--postgresql' 'sourcehut' 'psql.project' -# -# 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 -# -# REGENDATA ["--postgresql","sourcehut","psql.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.10.1 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_10_1-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.1 - - 8_10_1-check: | - cd example.org - cabal check - - 8_10_1-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_10_1-build: | - cd example.org - cabal build all - - 8_10_1-test: | - cd example.org - cabal test all --enable-tests - - 8_10_1-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.10.2 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--postgresql' 'sourcehut' 'psql.project' -# -# 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 -# -# REGENDATA ["--postgresql","sourcehut","psql.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.10.2 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_10_2-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.2 - - 8_10_2-check: | - cd example.org - cabal check - - 8_10_2-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_10_2-build: | - cd example.org - cabal build all - - 8_10_2-test: | - cd example.org - cabal test all --enable-tests - - 8_10_2-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.10.3 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--postgresql' 'sourcehut' 'psql.project' -# -# 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 -# -# REGENDATA ["--postgresql","sourcehut","psql.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.10.3 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_10_3-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.3 - - 8_10_3-check: | - cd example.org - cabal check - - 8_10_3-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_10_3-build: | - cd example.org - cabal build all - - 8_10_3-test: | - cd example.org - cabal test all --enable-tests - - 8_10_3-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.10.4 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--postgresql' 'sourcehut' 'psql.project' -# -# 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 -# -# REGENDATA ["--postgresql","sourcehut","psql.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.10.4 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_10_4-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.4 - - 8_10_4-check: | - cd example.org - cabal check - - 8_10_4-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_10_4-build: | - cd example.org - cabal build all - - 8_10_4-test: | - cd example.org - cabal test all --enable-tests - - 8_10_4-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.10.5 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--postgresql' 'sourcehut' 'psql.project' -# -# 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 -# -# REGENDATA ["--postgresql","sourcehut","psql.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.10.5 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_10_5-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.5 - - 8_10_5-check: | - cd example.org - cabal check - - 8_10_5-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_10_5-build: | - cd example.org - cabal build all - - 8_10_5-test: | - cd example.org - cabal test all --enable-tests - - 8_10_5-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.10.6 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--postgresql' 'sourcehut' 'psql.project' -# -# 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 -# -# REGENDATA ["--postgresql","sourcehut","psql.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.10.6 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_10_6-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.6 - - 8_10_6-check: | - cd example.org - cabal check - - 8_10_6-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_10_6-build: | - cd example.org - cabal build all - - 8_10_6-test: | - cd example.org - cabal test all --enable-tests - - 8_10_6-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.10.7 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--postgresql' 'sourcehut' 'psql.project' -# -# 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 -# -# REGENDATA ["--postgresql","sourcehut","psql.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.10.7 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_10_7-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.7 - - 8_10_7-check: | - cd example.org - cabal check - - 8_10_7-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_10_7-build: | - cd example.org - cabal build all - - 8_10_7-test: | - cd example.org - cabal test all --enable-tests - - 8_10_7-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.2.1 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--postgresql' 'sourcehut' 'psql.project' -# -# 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 -# -# REGENDATA ["--postgresql","sourcehut","psql.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.2.1 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_2_1-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.2.1 - - 8_2_1-check: | - cd example.org - cabal check - - 8_2_1-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_2_1-build: | - cd example.org - cabal build all - - 8_2_1-test: | - cd example.org - cabal test all --enable-tests - - 8_2_1-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.2.2 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--postgresql' 'sourcehut' 'psql.project' -# -# 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 -# -# REGENDATA ["--postgresql","sourcehut","psql.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.2.2 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_2_2-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.2.2 - - 8_2_2-check: | - cd example.org - cabal check - - 8_2_2-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_2_2-build: | - cd example.org - cabal build all - - 8_2_2-test: | - cd example.org - cabal test all --enable-tests - - 8_2_2-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.4.1 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--postgresql' 'sourcehut' 'psql.project' -# -# 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 -# -# REGENDATA ["--postgresql","sourcehut","psql.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.4.1 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_4_1-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.4.1 - - 8_4_1-check: | - cd example.org - cabal check - - 8_4_1-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_4_1-build: | - cd example.org - cabal build all - - 8_4_1-test: | - cd example.org - cabal test all --enable-tests - - 8_4_1-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.4.2 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--postgresql' 'sourcehut' 'psql.project' -# -# 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 -# -# REGENDATA ["--postgresql","sourcehut","psql.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.4.2 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_4_2-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.4.2 - - 8_4_2-check: | - cd example.org - cabal check - - 8_4_2-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_4_2-build: | - cd example.org - cabal build all - - 8_4_2-test: | - cd example.org - cabal test all --enable-tests - - 8_4_2-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.4.3 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--postgresql' 'sourcehut' 'psql.project' -# -# 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 -# -# REGENDATA ["--postgresql","sourcehut","psql.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.4.3 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_4_3-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.4.3 - - 8_4_3-check: | - cd example.org - cabal check - - 8_4_3-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_4_3-build: | - cd example.org - cabal build all - - 8_4_3-test: | - cd example.org - cabal test all --enable-tests - - 8_4_3-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.4.4 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--postgresql' 'sourcehut' 'psql.project' -# -# 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 -# -# REGENDATA ["--postgresql","sourcehut","psql.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.4.4 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_4_4-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.4.4 - - 8_4_4-check: | - cd example.org - cabal check - - 8_4_4-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_4_4-build: | - cd example.org - cabal build all - - 8_4_4-test: | - cd example.org - cabal test all --enable-tests - - 8_4_4-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.6.1 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--postgresql' 'sourcehut' 'psql.project' -# -# 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 -# -# REGENDATA ["--postgresql","sourcehut","psql.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.6.1 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_6_1-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.6.1 - - 8_6_1-check: | - cd example.org - cabal check - - 8_6_1-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_6_1-build: | - cd example.org - cabal build all - - 8_6_1-test: | - cd example.org - cabal test all --enable-tests - - 8_6_1-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.6.2 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--postgresql' 'sourcehut' 'psql.project' -# -# 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 -# -# REGENDATA ["--postgresql","sourcehut","psql.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.6.2 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_6_2-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.6.2 - - 8_6_2-check: | - cd example.org - cabal check - - 8_6_2-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_6_2-build: | - cd example.org - cabal build all - - 8_6_2-test: | - cd example.org - cabal test all --enable-tests - - 8_6_2-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.6.3 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--postgresql' 'sourcehut' 'psql.project' -# -# 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 -# -# REGENDATA ["--postgresql","sourcehut","psql.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.6.3 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_6_3-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.6.3 - - 8_6_3-check: | - cd example.org - cabal check - - 8_6_3-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_6_3-build: | - cd example.org - cabal build all - - 8_6_3-test: | - cd example.org - cabal test all --enable-tests - - 8_6_3-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.6.4 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--postgresql' 'sourcehut' 'psql.project' -# -# 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 -# -# REGENDATA ["--postgresql","sourcehut","psql.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.6.4 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_6_4-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.6.4 - - 8_6_4-check: | - cd example.org - cabal check - - 8_6_4-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_6_4-build: | - cd example.org - cabal build all - - 8_6_4-test: | - cd example.org - cabal test all --enable-tests - - 8_6_4-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.6.5 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--postgresql' 'sourcehut' 'psql.project' -# -# 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 -# -# REGENDATA ["--postgresql","sourcehut","psql.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.6.5 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_6_5-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.6.5 - - 8_6_5-check: | - cd example.org - cabal check - - 8_6_5-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_6_5-build: | - cd example.org - cabal build all - - 8_6_5-test: | - cd example.org - cabal test all --enable-tests - - 8_6_5-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.8.1 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--postgresql' 'sourcehut' 'psql.project' -# -# 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 -# -# REGENDATA ["--postgresql","sourcehut","psql.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.8.1 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_8_1-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.8.1 - - 8_8_1-check: | - cd example.org - cabal check - - 8_8_1-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_8_1-build: | - cd example.org - cabal build all - - 8_8_1-test: | - cd example.org - cabal test all --enable-tests - - 8_8_1-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.8.2 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--postgresql' 'sourcehut' 'psql.project' -# -# 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 -# -# REGENDATA ["--postgresql","sourcehut","psql.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.8.2 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_8_2-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.8.2 - - 8_8_2-check: | - cd example.org - cabal check - - 8_8_2-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_8_2-build: | - cd example.org - cabal build all - - 8_8_2-test: | - cd example.org - cabal test all --enable-tests - - 8_8_2-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.8.3 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--postgresql' 'sourcehut' 'psql.project' -# -# 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 -# -# REGENDATA ["--postgresql","sourcehut","psql.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.8.3 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_8_3-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.8.3 - - 8_8_3-check: | - cd example.org - cabal check - - 8_8_3-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_8_3-build: | - cd example.org - cabal build all - - 8_8_3-test: | - cd example.org - cabal test all --enable-tests - - 8_8_3-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.8.4 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--postgresql' 'sourcehut' 'psql.project' -# -# 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 -# -# REGENDATA ["--postgresql","sourcehut","psql.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.8.4 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_8_4-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.8.4 - - 8_8_4-check: | - cd example.org - cabal check - - 8_8_4-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_8_4-build: | - cd example.org - cabal build all - - 8_8_4-test: | - cd example.org - cabal test all --enable-tests - - 8_8_4-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com diff --git a/fixtures/psql.travis b/fixtures/psql.travis index d2386410..d65c70e7 100644 --- a/fixtures/psql.travis +++ b/fixtures/psql.travis @@ -2,7 +2,7 @@ # *INFO* Generating Travis-CI config for testing for GHC versions: 7.8.1 7.8.2 7.8.3 7.8.4 7.10.1 7.10.2 7.10.3 8.0.1 8.0.2 8.2.1 8.2.2 8.4.1 8.4.2 8.4.3 8.4.4 8.6.1 8.6.2 8.6.3 8.6.4 8.6.5 8.8.1 8.8.2 8.8.3 8.8.4 8.10.1 8.10.2 8.10.3 8.10.4 8.10.5 8.10.6 8.10.7 # This Travis job script has been generated by a script via # -# haskell-ci '--postgresql' 'travis' 'psql.project' +# haskell-ci '--postgresql' 'travis' 'psql.project' '--sourcehut-source' 'https://example.org' # # To regenerate the script (for example after adjusting tested-with) run # @@ -227,5 +227,5 @@ script: - rm -f cabal.project.local - ${CABAL} v2-build $WITHCOMPILER --disable-tests --disable-benchmarks all -# REGENDATA ["--postgresql","travis","psql.project"] +# REGENDATA ["--postgresql","travis","psql.project","--sourcehut-source","https://example.org"] # EOF diff --git a/fixtures/travis-patch.bash b/fixtures/travis-patch.bash index 2ab51386..d07891ad 100644 --- a/fixtures/travis-patch.bash +++ b/fixtures/travis-patch.bash @@ -2,7 +2,7 @@ # *INFO* Generating Bash script for testing for GHC versions: 7.8.1 7.8.2 7.8.3 7.8.4 7.10.1 7.10.2 7.10.3 8.0.1 8.0.2 8.2.1 8.2.2 8.4.1 8.4.2 8.4.3 8.4.4 8.6.1 8.6.2 8.6.3 8.6.4 8.6.5 8.8.1 8.8.2 8.8.3 8.8.4 8.10.1 8.10.2 8.10.3 8.10.4 8.10.5 8.10.6 8.10.7 #!/bin/bash # shellcheck disable=SC2086,SC2016,SC2046 -# REGENDATA ["--travis-patches=travis-patch.patch","bash","travis-patch.project"] +# REGENDATA ["--travis-patches=travis-patch.patch","bash","travis-patch.project","--sourcehut-source","https://example.org"] set -o pipefail diff --git a/fixtures/travis-patch.github b/fixtures/travis-patch.github index 811504a4..b2ead3fa 100644 --- a/fixtures/travis-patch.github +++ b/fixtures/travis-patch.github @@ -2,7 +2,7 @@ # *INFO* Generating GitHub config for testing for GHC versions: 7.8.1 7.8.2 7.8.3 7.8.4 7.10.1 7.10.2 7.10.3 8.0.1 8.0.2 8.2.1 8.2.2 8.4.1 8.4.2 8.4.3 8.4.4 8.6.1 8.6.2 8.6.3 8.6.4 8.6.5 8.8.1 8.8.2 8.8.3 8.8.4 8.10.1 8.10.2 8.10.3 8.10.4 8.10.5 8.10.6 8.10.7 # This GitHub workflow config has been generated by a script via # -# haskell-ci '--travis-patches=travis-patch.patch' 'github' 'travis-patch.project' +# haskell-ci '--travis-patches=travis-patch.patch' 'github' 'travis-patch.project' '--sourcehut-source' 'https://example.org' # # To regenerate the script (for example after adjusting tested-with) run # @@ -10,7 +10,7 @@ # # For more information, see https://github.com/haskell-CI/haskell-ci # -# REGENDATA ["--travis-patches=travis-patch.patch","github","travis-patch.project"] +# REGENDATA ["--travis-patches=travis-patch.patch","github","travis-patch.project","--sourcehut-source","https://example.org"] # name: Haskell-CI on: diff --git a/fixtures/travis-patch.sourcehut b/fixtures/travis-patch.sourcehut index 9f7768d2..320dee02 100644 --- a/fixtures/travis-patch.sourcehut +++ b/fixtures/travis-patch.sourcehut @@ -3,7 +3,7 @@ # manifest name: all # This Sourcehut job script has been generated by a script via # -# haskell-ci '--travis-patches=travis-patch.patch' 'sourcehut' 'travis-patch.project' +# haskell-ci '--travis-patches=travis-patch.patch' 'sourcehut' 'travis-patch.project' '--sourcehut-source' 'https://example.org' # # To regenerate the script (for example after adjusting tested-with) run # @@ -11,7 +11,7 @@ # # For more information, see https://github.com/haskell-CI/haskell-ci # -# REGENDATA ["--travis-patches=travis-patch.patch","sourcehut","travis-patch.project"] +# REGENDATA ["--travis-patches=travis-patch.patch","sourcehut","travis-patch.project","--sourcehut-source","https://example.org"] # image: ubuntu/bionic packages: diff --git a/fixtures/travis-patch.sourcehut-parallel b/fixtures/travis-patch.sourcehut-parallel deleted file mode 100644 index e0d309e9..00000000 --- a/fixtures/travis-patch.sourcehut-parallel +++ /dev/null @@ -1,1552 +0,0 @@ -# SUCCESS -# *INFO* Generating Sourcehut config for testing for GHC versions: 7.8.1 7.8.2 7.8.3 7.8.4 7.10.1 7.10.2 7.10.3 8.0.1 8.0.2 8.2.1 8.2.2 8.4.1 8.4.2 8.4.3 8.4.4 8.6.1 8.6.2 8.6.3 8.6.4 8.6.5 8.8.1 8.8.2 8.8.3 8.8.4 8.10.1 8.10.2 8.10.3 8.10.4 8.10.5 8.10.6 8.10.7 -# manifest name: 7.10.1 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--travis-patches=travis-patch.patch' 'sourcehut' 'travis-patch.project' -# -# 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 -# -# REGENDATA ["--travis-patches=travis-patch.patch","sourcehut","travis-patch.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-7.10.1 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 7_10_1-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.10.1 - - 7_10_1-check: | - cd example.org - cabal check - - 7_10_1-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 7_10_1-build: | - cd example.org - cabal build all - - 7_10_1-test: | - cd example.org - cabal test all --enable-tests - - 7_10_1-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 7.10.2 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--travis-patches=travis-patch.patch' 'sourcehut' 'travis-patch.project' -# -# 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 -# -# REGENDATA ["--travis-patches=travis-patch.patch","sourcehut","travis-patch.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-7.10.2 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 7_10_2-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.10.2 - - 7_10_2-check: | - cd example.org - cabal check - - 7_10_2-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 7_10_2-build: | - cd example.org - cabal build all - - 7_10_2-test: | - cd example.org - cabal test all --enable-tests - - 7_10_2-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 7.10.3 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--travis-patches=travis-patch.patch' 'sourcehut' 'travis-patch.project' -# -# 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 -# -# REGENDATA ["--travis-patches=travis-patch.patch","sourcehut","travis-patch.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-7.10.3 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 7_10_3-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.10.3 - - 7_10_3-check: | - cd example.org - cabal check - - 7_10_3-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 7_10_3-build: | - cd example.org - cabal build all - - 7_10_3-test: | - cd example.org - cabal test all --enable-tests - - 7_10_3-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 7.8.1 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--travis-patches=travis-patch.patch' 'sourcehut' 'travis-patch.project' -# -# 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 -# -# REGENDATA ["--travis-patches=travis-patch.patch","sourcehut","travis-patch.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-7.8.1 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 7_8_1-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.8.1 - - 7_8_1-check: | - cd example.org - cabal check - - 7_8_1-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 7_8_1-build: | - cd example.org - cabal build all - - 7_8_1-test: | - cd example.org - cabal test all --enable-tests - - 7_8_1-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 7.8.2 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--travis-patches=travis-patch.patch' 'sourcehut' 'travis-patch.project' -# -# 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 -# -# REGENDATA ["--travis-patches=travis-patch.patch","sourcehut","travis-patch.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-7.8.2 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 7_8_2-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.8.2 - - 7_8_2-check: | - cd example.org - cabal check - - 7_8_2-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 7_8_2-build: | - cd example.org - cabal build all - - 7_8_2-test: | - cd example.org - cabal test all --enable-tests - - 7_8_2-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 7.8.3 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--travis-patches=travis-patch.patch' 'sourcehut' 'travis-patch.project' -# -# 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 -# -# REGENDATA ["--travis-patches=travis-patch.patch","sourcehut","travis-patch.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-7.8.3 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 7_8_3-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.8.3 - - 7_8_3-check: | - cd example.org - cabal check - - 7_8_3-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 7_8_3-build: | - cd example.org - cabal build all - - 7_8_3-test: | - cd example.org - cabal test all --enable-tests - - 7_8_3-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 7.8.4 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--travis-patches=travis-patch.patch' 'sourcehut' 'travis-patch.project' -# -# 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 -# -# REGENDATA ["--travis-patches=travis-patch.patch","sourcehut","travis-patch.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-7.8.4 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 7_8_4-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.8.4 - - 7_8_4-check: | - cd example.org - cabal check - - 7_8_4-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 7_8_4-build: | - cd example.org - cabal build all - - 7_8_4-test: | - cd example.org - cabal test all --enable-tests - - 7_8_4-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.0.1 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--travis-patches=travis-patch.patch' 'sourcehut' 'travis-patch.project' -# -# 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 -# -# REGENDATA ["--travis-patches=travis-patch.patch","sourcehut","travis-patch.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.0.1 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_0_1-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.0.1 - - 8_0_1-check: | - cd example.org - cabal check - - 8_0_1-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_0_1-build: | - cd example.org - cabal build all - - 8_0_1-test: | - cd example.org - cabal test all --enable-tests - - 8_0_1-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.0.2 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--travis-patches=travis-patch.patch' 'sourcehut' 'travis-patch.project' -# -# 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 -# -# REGENDATA ["--travis-patches=travis-patch.patch","sourcehut","travis-patch.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.0.2 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_0_2-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.0.2 - - 8_0_2-check: | - cd example.org - cabal check - - 8_0_2-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_0_2-build: | - cd example.org - cabal build all - - 8_0_2-test: | - cd example.org - cabal test all --enable-tests - - 8_0_2-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.10.1 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--travis-patches=travis-patch.patch' 'sourcehut' 'travis-patch.project' -# -# 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 -# -# REGENDATA ["--travis-patches=travis-patch.patch","sourcehut","travis-patch.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.10.1 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_10_1-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.1 - - 8_10_1-check: | - cd example.org - cabal check - - 8_10_1-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_10_1-build: | - cd example.org - cabal build all - - 8_10_1-test: | - cd example.org - cabal test all --enable-tests - - 8_10_1-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.10.2 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--travis-patches=travis-patch.patch' 'sourcehut' 'travis-patch.project' -# -# 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 -# -# REGENDATA ["--travis-patches=travis-patch.patch","sourcehut","travis-patch.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.10.2 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_10_2-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.2 - - 8_10_2-check: | - cd example.org - cabal check - - 8_10_2-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_10_2-build: | - cd example.org - cabal build all - - 8_10_2-test: | - cd example.org - cabal test all --enable-tests - - 8_10_2-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.10.3 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--travis-patches=travis-patch.patch' 'sourcehut' 'travis-patch.project' -# -# 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 -# -# REGENDATA ["--travis-patches=travis-patch.patch","sourcehut","travis-patch.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.10.3 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_10_3-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.3 - - 8_10_3-check: | - cd example.org - cabal check - - 8_10_3-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_10_3-build: | - cd example.org - cabal build all - - 8_10_3-test: | - cd example.org - cabal test all --enable-tests - - 8_10_3-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.10.4 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--travis-patches=travis-patch.patch' 'sourcehut' 'travis-patch.project' -# -# 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 -# -# REGENDATA ["--travis-patches=travis-patch.patch","sourcehut","travis-patch.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.10.4 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_10_4-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.4 - - 8_10_4-check: | - cd example.org - cabal check - - 8_10_4-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_10_4-build: | - cd example.org - cabal build all - - 8_10_4-test: | - cd example.org - cabal test all --enable-tests - - 8_10_4-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.10.5 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--travis-patches=travis-patch.patch' 'sourcehut' 'travis-patch.project' -# -# 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 -# -# REGENDATA ["--travis-patches=travis-patch.patch","sourcehut","travis-patch.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.10.5 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_10_5-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.5 - - 8_10_5-check: | - cd example.org - cabal check - - 8_10_5-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_10_5-build: | - cd example.org - cabal build all - - 8_10_5-test: | - cd example.org - cabal test all --enable-tests - - 8_10_5-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.10.6 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--travis-patches=travis-patch.patch' 'sourcehut' 'travis-patch.project' -# -# 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 -# -# REGENDATA ["--travis-patches=travis-patch.patch","sourcehut","travis-patch.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.10.6 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_10_6-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.6 - - 8_10_6-check: | - cd example.org - cabal check - - 8_10_6-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_10_6-build: | - cd example.org - cabal build all - - 8_10_6-test: | - cd example.org - cabal test all --enable-tests - - 8_10_6-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.10.7 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--travis-patches=travis-patch.patch' 'sourcehut' 'travis-patch.project' -# -# 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 -# -# REGENDATA ["--travis-patches=travis-patch.patch","sourcehut","travis-patch.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.10.7 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_10_7-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.7 - - 8_10_7-check: | - cd example.org - cabal check - - 8_10_7-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_10_7-build: | - cd example.org - cabal build all - - 8_10_7-test: | - cd example.org - cabal test all --enable-tests - - 8_10_7-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.2.1 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--travis-patches=travis-patch.patch' 'sourcehut' 'travis-patch.project' -# -# 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 -# -# REGENDATA ["--travis-patches=travis-patch.patch","sourcehut","travis-patch.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.2.1 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_2_1-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.2.1 - - 8_2_1-check: | - cd example.org - cabal check - - 8_2_1-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_2_1-build: | - cd example.org - cabal build all - - 8_2_1-test: | - cd example.org - cabal test all --enable-tests - - 8_2_1-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.2.2 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--travis-patches=travis-patch.patch' 'sourcehut' 'travis-patch.project' -# -# 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 -# -# REGENDATA ["--travis-patches=travis-patch.patch","sourcehut","travis-patch.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.2.2 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_2_2-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.2.2 - - 8_2_2-check: | - cd example.org - cabal check - - 8_2_2-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_2_2-build: | - cd example.org - cabal build all - - 8_2_2-test: | - cd example.org - cabal test all --enable-tests - - 8_2_2-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.4.1 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--travis-patches=travis-patch.patch' 'sourcehut' 'travis-patch.project' -# -# 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 -# -# REGENDATA ["--travis-patches=travis-patch.patch","sourcehut","travis-patch.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.4.1 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_4_1-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.4.1 - - 8_4_1-check: | - cd example.org - cabal check - - 8_4_1-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_4_1-build: | - cd example.org - cabal build all - - 8_4_1-test: | - cd example.org - cabal test all --enable-tests - - 8_4_1-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.4.2 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--travis-patches=travis-patch.patch' 'sourcehut' 'travis-patch.project' -# -# 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 -# -# REGENDATA ["--travis-patches=travis-patch.patch","sourcehut","travis-patch.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.4.2 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_4_2-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.4.2 - - 8_4_2-check: | - cd example.org - cabal check - - 8_4_2-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_4_2-build: | - cd example.org - cabal build all - - 8_4_2-test: | - cd example.org - cabal test all --enable-tests - - 8_4_2-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.4.3 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--travis-patches=travis-patch.patch' 'sourcehut' 'travis-patch.project' -# -# 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 -# -# REGENDATA ["--travis-patches=travis-patch.patch","sourcehut","travis-patch.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.4.3 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_4_3-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.4.3 - - 8_4_3-check: | - cd example.org - cabal check - - 8_4_3-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_4_3-build: | - cd example.org - cabal build all - - 8_4_3-test: | - cd example.org - cabal test all --enable-tests - - 8_4_3-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.4.4 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--travis-patches=travis-patch.patch' 'sourcehut' 'travis-patch.project' -# -# 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 -# -# REGENDATA ["--travis-patches=travis-patch.patch","sourcehut","travis-patch.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.4.4 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_4_4-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.4.4 - - 8_4_4-check: | - cd example.org - cabal check - - 8_4_4-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_4_4-build: | - cd example.org - cabal build all - - 8_4_4-test: | - cd example.org - cabal test all --enable-tests - - 8_4_4-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.6.1 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--travis-patches=travis-patch.patch' 'sourcehut' 'travis-patch.project' -# -# 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 -# -# REGENDATA ["--travis-patches=travis-patch.patch","sourcehut","travis-patch.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.6.1 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_6_1-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.6.1 - - 8_6_1-check: | - cd example.org - cabal check - - 8_6_1-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_6_1-build: | - cd example.org - cabal build all - - 8_6_1-test: | - cd example.org - cabal test all --enable-tests - - 8_6_1-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.6.2 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--travis-patches=travis-patch.patch' 'sourcehut' 'travis-patch.project' -# -# 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 -# -# REGENDATA ["--travis-patches=travis-patch.patch","sourcehut","travis-patch.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.6.2 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_6_2-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.6.2 - - 8_6_2-check: | - cd example.org - cabal check - - 8_6_2-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_6_2-build: | - cd example.org - cabal build all - - 8_6_2-test: | - cd example.org - cabal test all --enable-tests - - 8_6_2-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.6.3 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--travis-patches=travis-patch.patch' 'sourcehut' 'travis-patch.project' -# -# 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 -# -# REGENDATA ["--travis-patches=travis-patch.patch","sourcehut","travis-patch.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.6.3 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_6_3-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.6.3 - - 8_6_3-check: | - cd example.org - cabal check - - 8_6_3-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_6_3-build: | - cd example.org - cabal build all - - 8_6_3-test: | - cd example.org - cabal test all --enable-tests - - 8_6_3-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.6.4 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--travis-patches=travis-patch.patch' 'sourcehut' 'travis-patch.project' -# -# 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 -# -# REGENDATA ["--travis-patches=travis-patch.patch","sourcehut","travis-patch.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.6.4 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_6_4-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.6.4 - - 8_6_4-check: | - cd example.org - cabal check - - 8_6_4-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_6_4-build: | - cd example.org - cabal build all - - 8_6_4-test: | - cd example.org - cabal test all --enable-tests - - 8_6_4-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.6.5 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--travis-patches=travis-patch.patch' 'sourcehut' 'travis-patch.project' -# -# 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 -# -# REGENDATA ["--travis-patches=travis-patch.patch","sourcehut","travis-patch.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.6.5 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_6_5-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.6.5 - - 8_6_5-check: | - cd example.org - cabal check - - 8_6_5-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_6_5-build: | - cd example.org - cabal build all - - 8_6_5-test: | - cd example.org - cabal test all --enable-tests - - 8_6_5-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.8.1 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--travis-patches=travis-patch.patch' 'sourcehut' 'travis-patch.project' -# -# 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 -# -# REGENDATA ["--travis-patches=travis-patch.patch","sourcehut","travis-patch.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.8.1 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_8_1-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.8.1 - - 8_8_1-check: | - cd example.org - cabal check - - 8_8_1-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_8_1-build: | - cd example.org - cabal build all - - 8_8_1-test: | - cd example.org - cabal test all --enable-tests - - 8_8_1-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.8.2 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--travis-patches=travis-patch.patch' 'sourcehut' 'travis-patch.project' -# -# 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 -# -# REGENDATA ["--travis-patches=travis-patch.patch","sourcehut","travis-patch.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.8.2 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_8_2-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.8.2 - - 8_8_2-check: | - cd example.org - cabal check - - 8_8_2-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_8_2-build: | - cd example.org - cabal build all - - 8_8_2-test: | - cd example.org - cabal test all --enable-tests - - 8_8_2-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.8.3 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--travis-patches=travis-patch.patch' 'sourcehut' 'travis-patch.project' -# -# 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 -# -# REGENDATA ["--travis-patches=travis-patch.patch","sourcehut","travis-patch.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.8.3 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_8_3-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.8.3 - - 8_8_3-check: | - cd example.org - cabal check - - 8_8_3-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_8_3-build: | - cd example.org - cabal build all - - 8_8_3-test: | - cd example.org - cabal test all --enable-tests - - 8_8_3-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com -# manifest name: 8.8.4 -# This Sourcehut job script has been generated by a script via -# -# haskell-ci '--travis-patches=travis-patch.patch' 'sourcehut' 'travis-patch.project' -# -# 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 -# -# REGENDATA ["--travis-patches=travis-patch.patch","sourcehut","travis-patch.project"] -# -image: ubuntu/bionic -packages: - - gcc - - cabal-install-3.4 - - ghc-8.8.4 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 -sources: - - https://example.org -tasks: - - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv - cabal update - - 8_8_4-prepare: | - cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.8.4 - - 8_8_4-check: | - cd example.org - cabal check - - 8_8_4-dependencies: | - cd example.org - cabal build all --enable-tests --only-dependencies - cabal build all --only-dependencies - - 8_8_4-build: | - cd example.org - cabal build all - - 8_8_4-test: | - cd example.org - cabal test all --enable-tests - - 8_8_4-haddock: | - cd example.org - cabal haddock all -triggers: - - action: email - condition: failure - to: haskell-servant-maintainers@googlegroups.com diff --git a/fixtures/travis-patch.travis b/fixtures/travis-patch.travis index 8c1a7575..2b90765f 100644 --- a/fixtures/travis-patch.travis +++ b/fixtures/travis-patch.travis @@ -2,7 +2,7 @@ # *INFO* Generating Travis-CI config for testing for GHC versions: 7.8.1 7.8.2 7.8.3 7.8.4 7.10.1 7.10.2 7.10.3 8.0.1 8.0.2 8.2.1 8.2.2 8.4.1 8.4.2 8.4.3 8.4.4 8.6.1 8.6.2 8.6.3 8.6.4 8.6.5 8.8.1 8.8.2 8.8.3 8.8.4 8.10.1 8.10.2 8.10.3 8.10.4 8.10.5 8.10.6 8.10.7 # This Travis job script has been generated by a script via # -# haskell-ci '--travis-patches=travis-patch.patch' 'travis' 'travis-patch.project' +# haskell-ci '--travis-patches=travis-patch.patch' 'travis' 'travis-patch.project' '--sourcehut-source' 'https://example.org' # # To regenerate the script (for example after adjusting tested-with) run # @@ -223,5 +223,5 @@ script: - rm -f cabal.project.local - ${CABAL} v2-build $WITHCOMPILER --disable-tests --disable-benchmarks all -# REGENDATA ["--travis-patches=travis-patch.patch","travis","travis-patch.project"] +# REGENDATA ["--travis-patches=travis-patch.patch","travis","travis-patch.project","--sourcehut-source","https://example.org"] # EOF diff --git a/src/HaskellCI.hs b/src/HaskellCI.hs index 5d893e8e..e233bde6 100644 --- a/src/HaskellCI.hs +++ b/src/HaskellCI.hs @@ -51,7 +51,6 @@ import qualified Data.ByteString as BS import qualified Data.List.NonEmpty as NE import qualified Data.Map as Map import qualified Data.Set as S -import qualified Data.Text as TS import qualified Data.Traversable as T import qualified Distribution.Compiler as Compiler import qualified Distribution.Package as Pkg @@ -103,10 +102,10 @@ main = do regenerateTravis opts regenerateSourcehut opts - CommandBash f -> doBash argv0 f opts - CommandGitHub f -> doGitHub argv0 f opts - CommandTravis f -> doTravis argv0 f opts - CommandSourcehut srhtOpts -> doSourcehut argv0 srhtOpts opts + CommandBash f -> doBash argv0 f opts + CommandGitHub f -> doGitHub argv0 f opts + CommandTravis f -> doTravis argv0 f opts + CommandSourcehut f -> doSourcehut argv0 f opts CommandVersionInfo -> do putStrLn $ "haskell-ci " ++ haskellCIVerStr ++ " with dependencies" @@ -385,9 +384,9 @@ regenerateGitHub opts = do defaultSourcehutPath :: FilePath defaultSourcehutPath = ".builds" -doSourcehut :: [String] -> SourcehutOptions (Maybe String) -> Options -> IO () -doSourcehut args srhtOpts opts = do - contents <- sourcehutFromConfigFile args opts srhtOpts +doSourcehut :: [String] -> FilePath -> Options -> IO () +doSourcehut args path opts = do + contents <- sourcehutFromConfigFile args opts path case optOutput opts of Nothing -> do createDir defaultSourcehutPath @@ -407,11 +406,11 @@ sourcehutFromConfigFile :: forall m. (MonadIO m, MonadDiagnostics m, MonadMask m) => [String] -> Options - -> SourcehutOptions (Maybe String) + -> FilePath -> m (M.Map FilePath ByteString) -sourcehutFromConfigFile args opts srhtOpts@SourcehutOptions{sourcehutOptPath} = do +sourcehutFromConfigFile args opts path = do gitconfig <- liftIO readGitConfig - cabalFiles <- getCabalFiles (optInputType' opts sourcehutOptPath) sourcehutOptPath + cabalFiles <- getCabalFiles (optInputType' opts path) path config' <- findConfigFile (optConfig opts) let config = optConfigMorphism opts config' pkgs <- T.mapM (configFromCabalFile config) cabalFiles @@ -423,7 +422,7 @@ sourcehutFromConfigFile args opts srhtOpts@SourcehutOptions{sourcehutOptPath} = let prj' | cfgGhcHead config = over (mapped . field @"pkgJobs") (S.insert GHCHead) prj | otherwise = prj - ls <- genSourcehutFromConfigs args config gitconfig srhtOpts prj' ghcs + ls <- genSourcehutFromConfigs args config gitconfig prj' ghcs return ls -- TODO patchSourcehut config ls genSourcehutFromConfigs @@ -431,26 +430,12 @@ genSourcehutFromConfigs => [String] -> Config -> GitConfig - -> SourcehutOptions (Maybe String) -> Project URI Void Package -> Set CompilerVersion -> m (M.Map FilePath ByteString) -genSourcehutFromConfigs argv config gitconfig srhtOpts@SourcehutOptions{sourcehutOptSource} prj vs = do +genSourcehutFromConfigs argv config gitconfig prj vs = do let jobVersions = makeJobVersions config vs - gitRemote = case M.toList (gitCfgRemotes gitconfig) of - [(_,url)] -> Just url - -- In case of multiple remotes, pick origin - -- MAYBE just pick the first instead? - rs -> case filter (("origin" ==) . fst) rs of - (_,url) : _ -> Just url - [] -> Nothing - sourcehutOptSource' <- case sourcehutOptSource of - Just url -> return url - Nothing -> case gitRemote of - Just url -> return $ TS.unpack url - Nothing -> putStrLnErr "multiple/no remotes found and --sourcehut-source was not used" - let srhtOpts' = srhtOpts {sourcehutOptSource = sourcehutOptSource'} - case makeSourcehut argv config srhtOpts' prj jobVersions of + case makeSourcehut argv config gitconfig prj jobVersions of Left err -> putStrLnErr $ displayException err Right sourcehut -> do describeJobs "Sourcehut config" (cfgTestedWith config) jobVersions (prjPackages prj) @@ -479,8 +464,8 @@ regenerateSourcehut opts = do -- Warn about outdated .yml files. to be safe, we don't delete them all. putStrLnWarn "Outdated .yml files will not be deleted" - (srhtOpts, opts') <- parseOptionsSrht argv - doSourcehut argv srhtOpts ( opts' <> opts) + (f, opts') <- parseOptions argv + doSourcehut argv f ( optionsWithOutputFile fp <> opts' <> opts) where noSourcehutScript :: IO () noSourcehutScript = putStrLn $ "No " ++ defaultSourcehutPath ++ "/*.yml or .build.yml, skipping Sourcehut config regeneration" diff --git a/src/HaskellCI/Cli.hs b/src/HaskellCI/Cli.hs index 5a70d7cf..8026a816 100644 --- a/src/HaskellCI/Cli.hs +++ b/src/HaskellCI/Cli.hs @@ -5,7 +5,6 @@ module HaskellCI.Cli where import HaskellCI.Prelude -import Control.Applicative (optional) import System.Exit (exitFailure) import System.FilePath.Posix (takeFileName) import System.IO (hPutStrLn, stderr) @@ -14,7 +13,6 @@ import qualified Options.Applicative as O import HaskellCI.Config import HaskellCI.OptparseGrammar -import HaskellCI.Sourcehut (SourcehutOptions(..)) import HaskellCI.VersionInfo ------------------------------------------------------------------------------- @@ -25,7 +23,7 @@ data Command = CommandTravis FilePath | CommandBash FilePath | CommandGitHub FilePath - | CommandSourcehut (SourcehutOptions (Maybe String)) + | CommandSourcehut FilePath | CommandRegenerate | CommandListGHC | CommandDumpConfig @@ -151,14 +149,8 @@ cliParserInfo = O.info ((,) <$> cmdP <*> optionsP O.<**> versionP O.<**> O.helpe githubP = CommandGitHub <$> O.strArgument (O.metavar "CABAL.FILE" <> O.action "file" <> O.help "Either or cabal.project") - sourcehutP = fmap CommandSourcehut $ SourcehutOptions + sourcehutP = CommandSourcehut <$> O.strArgument (O.metavar "CABAL.FILE" <> O.action "file" <> O.help "Either or cabal.project") - <*> optional (O.strOption (O.long "source" <> O.metavar "URI" <> O.help "The source to test (default: from git remote)")) - <*> O.switch (O.long "sourcehut-parallel" <> O.help ( - "In Sourcehut, use many manifests to run jobs in parallel. " <> - "Disabled by default because in the sr.ht instance a maximum of " <> - "4 parallel jobs are allowed." - )) ------------------------------------------------------------------------------- -- Parsing helpers @@ -176,19 +168,8 @@ parseOptions argv = case res of res = O.execParserPure (O.prefs O.subparserInline) cliParserInfo argv fromCmd :: Command -> IO FilePath - fromCmd (CommandTravis fp) = return fp - fromCmd (CommandBash fp) = return fp - fromCmd (CommandGitHub fp) = return fp - fromCmd (CommandSourcehut srhtOpts) = return $ sourcehutOptPath srhtOpts - fromCmd cmd = fail $ "Command without filepath: " ++ show cmd - --- TODO find a way to merge this with the above... or use global options only -parseOptionsSrht :: [String] -> IO (SourcehutOptions (Maybe String), Options) -parseOptionsSrht argv = case res of - O.Success (CommandSourcehut cmd, opts) -> return (cmd, opts) - O.Success _ -> fail "parseOptionsSrht on non-sourcehut command" - O.Failure f -> case O.renderFailure f "haskell-ci" of - (help, _) -> hPutStrLn stderr help >> exitFailure - O.CompletionInvoked _ -> exitFailure -- unexpected - where - res = O.execParserPure (O.prefs O.subparserInline) cliParserInfo argv + fromCmd (CommandTravis fp) = return fp + fromCmd (CommandBash fp) = return fp + fromCmd (CommandGitHub fp) = return fp + fromCmd (CommandSourcehut fp) = return fp + fromCmd cmd = fail $ "Command without filepath: " ++ show cmd diff --git a/src/HaskellCI/Config.hs b/src/HaskellCI/Config.hs index 8fd8ec36..7d7c3650 100644 --- a/src/HaskellCI/Config.hs +++ b/src/HaskellCI/Config.hs @@ -103,6 +103,8 @@ data Config = Config , cfgRawTravis :: !String , cfgGitHubActionName :: !(Maybe String) , cfgTimeoutMinutes :: !Natural + , cfgSourcehutSource :: !(Maybe String) + , cfgSourcehutParallel :: !Bool } deriving (Generic) @@ -247,6 +249,12 @@ configGrammar = Config ^^^ help "The name of GitHub Action" <*> C.optionalFieldDef "timeout-minutes" (field @"cfgTimeoutMinutes") 60 ^^^ metahelp "MINUTES" "The maximum number of minutes to let a job run" + <*> C.freeTextField "sourcehut-source" (field @"cfgSourcehutSource") + ^^^ metahelp "URI" "The source to test (default: from git remote)" + <*> C.booleanFieldDef "sourcehut-parallel" (field @"cfgSourcehutParallel") False + ^^^ help "In Sourcehut, use many manifests to run jobs in parallel. \ + \Disabled by default because in the sr.ht instance a maximum of \ + \4 parallel jobs are allowed." ------------------------------------------------------------------------------- -- Reading diff --git a/src/HaskellCI/Sourcehut.hs b/src/HaskellCI/Sourcehut.hs index 7bbae2c4..424cf9c1 100644 --- a/src/HaskellCI/Sourcehut.hs +++ b/src/HaskellCI/Sourcehut.hs @@ -3,7 +3,6 @@ {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE RecordWildCards #-} module HaskellCI.Sourcehut ( - SourcehutOptions(..), makeSourcehut, sourcehutHeader, ) where @@ -13,6 +12,7 @@ import HaskellCI.Prelude import Data.Containers.ListUtils (nubOrd) import qualified Data.Map.Strict as M import qualified Data.Set as S +import qualified Data.Text as T import qualified Distribution.Pretty as C import qualified Distribution.Types.GenericPackageDescription as C import qualified Distribution.Types.PackageDescription as C @@ -24,6 +24,7 @@ import Cabal.Project import HaskellCI.Auxiliary import HaskellCI.Compiler import HaskellCI.Config +import HaskellCI.GitConfig import HaskellCI.Jobs import HaskellCI.List import HaskellCI.Package @@ -31,16 +32,6 @@ import HaskellCI.Sh import HaskellCI.Sourcehut.Yaml import HaskellCI.VersionInfo -------------------------------------------------------------------------------- --- Sourcehut options -------------------------------------------------------------------------------- - -data SourcehutOptions src = SourcehutOptions - { sourcehutOptPath :: FilePath - , sourcehutOptSource :: src - , sourcehutOptParallel :: Bool - } - deriving Show ------------------------------------------------------------------------------- -- Sourcehut header @@ -84,13 +75,34 @@ Sourcehut–specific notes: makeSourcehut :: [String] -> Config - -> SourcehutOptions String + -> GitConfig + -> Project URI Void Package + -> JobVersions + -> Either HsCiError Sourcehut +makeSourcehut _argv config@Config {..} gitconfig prj jobs = do + let gitRemote = case M.toList (gitCfgRemotes gitconfig) of + [(_,url)] -> Just url + -- In case of multiple remotes, pick origin + -- MAYBE just pick the first instead? + rs -> case filter (("origin" ==) . fst) rs of + (_,url) : _ -> Just url + [] -> Nothing + source <- case cfgSourcehutSource of + Just url -> return url + Nothing -> case gitRemote of + Just url -> return $ T.unpack url + Nothing -> Left $ ValidationError "multiple/no remotes found and --sourcehut-source was not used" + makeSourcehut' config source prj jobs + +makeSourcehut' + :: Config + -> String -> Project URI Void Package -> JobVersions -> Either HsCiError Sourcehut -makeSourcehut _argv config@Config {..} SourcehutOptions {..} prj jobs@JobVersions {..} = +makeSourcehut' config@Config {..} source prj jobs@JobVersions {..} = Sourcehut <$> - if sourcehutOptParallel + if cfgSourcehutParallel then parallelManifests else M.singleton "all" <$> sequentialManifest where @@ -120,14 +132,14 @@ makeSourcehut _argv config@Config {..} SourcehutOptions {..} prj jobs@JobVersion "hvr-ghc" ("http://ppa.launchpad.net/hvr/ghc/ubuntu " ++ C.prettyShow cfgUbuntu ++ " main ff3aeacef6f88286") , srhtManifestArtifacts = [] - , srhtManifestSources = [sourcehutOptSource] + , srhtManifestSources = [source] , srhtManifestTasks = prepare : tasks , srhtManifestTriggers = SourcehutTriggerEmail <$> nubOrd (getEmails prj) , srhtManifestEnvironment = mempty } clonePath :: FilePath - clonePath = removeSuffix ".git" $ takeFileName sourcehutOptSource + clonePath = removeSuffix ".git" $ takeFileName $ source -- MAYBE reader for job and clonePath mkTasksForGhc :: CompilerVersion -> Either HsCiError [SourcehutTask] diff --git a/test/Tests.hs b/test/Tests.hs index 976c81a9..c6d7859f 100644 --- a/test/Tests.hs +++ b/test/Tests.hs @@ -5,7 +5,6 @@ import Prelude () import Prelude.Compat import HaskellCI hiding (main) -import HaskellCI.Sourcehut (SourcehutOptions(..)) import Control.Arrow (first) import Data.Algorithm.Diff (PolyDiff (..), getGroupedDiff) @@ -47,29 +46,25 @@ main = do -- @ fixtureGoldenTest :: FilePath -> TestTree fixtureGoldenTest fp = testGroup fp - [ fixtureGoldenTest' "travis" "travis" travisFromConfigFile - , fixtureGoldenTest' "github" "github" githubFromConfigFile - , fixtureGoldenTest' "bash" "bash" bashFromConfigFile - , fixtureGoldenTest' "sourcehut" "sourcehut" (sourcehutFromConfigFile' False) - , fixtureGoldenTest' "sourcehut-parallel" "sourcehut" (sourcehutFromConfigFile' True) + [ fixtureGoldenTest' "travis" travisFromConfigFile + , fixtureGoldenTest' "github" githubFromConfigFile + , fixtureGoldenTest' "bash" bashFromConfigFile + , fixtureGoldenTest' "sourcehut" sourcehutFromConfigFile' ] where - sourcehutFromConfigFile' parallel argv opts projectfp = + sourcehutFromConfigFile' argv opts projectfp = BS.concat <$> fmap addSourcehutHeader <$> Map.toList <$> - sourcehutFromConfigFile argv opts SourcehutOptions - { sourcehutOptPath = projectfp - , sourcehutOptSource = Just "https://example.org" - , sourcehutOptParallel = parallel - } + sourcehutFromConfigFile argv opts projectfp addSourcehutHeader :: (FilePath, BS.ByteString) -> BS.ByteString addSourcehutHeader (n, m) = BS8.pack ("# manifest name: " <> n <> "\n") <> m - fixtureGoldenTest' name command generate = cabalGoldenTest name outputRef $ do + -- name acts as extension also + fixtureGoldenTest' name generate = cabalGoldenTest name outputRef $ do (argv, opts') <- makeFlags let opts = opts' - { optInputType = Just InputTypeProject - , optConfigMorphism = (\cfg -> cfg { cfgInsertVersion = False}) . optConfigMorphism opts' + { optInputType = Just InputTypeProject + , optConfigMorphism = (\cfg -> cfg { cfgInsertVersion = False}) . optConfigMorphism opts' } let genConfig = generate argv opts projectfp first (fmap (lines . fromUTF8BS)) <$> runDiagnosticsT genConfig @@ -85,7 +80,7 @@ fixtureGoldenTest fp = testGroup fp makeFlags :: IO ([String], Options) makeFlags = do argv <- readArgv - let argv' = argv ++ [command, projectfp] + let argv' = argv ++ [name, projectfp] ++ ["--sourcehut-source", "https://example.org"] (_fp, opts) <- parseOptions argv' return (argv', opts) From 167b600721da46371d0d2e344716ebcadd715c38 Mon Sep 17 00:00:00 2001 From: Francesco Gazzetta Date: Mon, 29 Nov 2021 20:56:31 +0100 Subject: [PATCH 16/23] sourcehut: add --parallel test --- fixtures/sourcehut-parallel.args | 1 + fixtures/sourcehut-parallel.bash | 520 +++++++++ fixtures/sourcehut-parallel.github | 352 ++++++ fixtures/sourcehut-parallel.project | 1 + fixtures/sourcehut-parallel.sourcehut | 1552 +++++++++++++++++++++++++ fixtures/sourcehut-parallel.travis | 227 ++++ test/Tests.hs | 1 + 7 files changed, 2654 insertions(+) create mode 100644 fixtures/sourcehut-parallel.args create mode 100644 fixtures/sourcehut-parallel.bash create mode 100644 fixtures/sourcehut-parallel.github create mode 100644 fixtures/sourcehut-parallel.project create mode 100644 fixtures/sourcehut-parallel.sourcehut create mode 100644 fixtures/sourcehut-parallel.travis diff --git a/fixtures/sourcehut-parallel.args b/fixtures/sourcehut-parallel.args new file mode 100644 index 00000000..7fae0611 --- /dev/null +++ b/fixtures/sourcehut-parallel.args @@ -0,0 +1 @@ +--sourcehut-parallel diff --git a/fixtures/sourcehut-parallel.bash b/fixtures/sourcehut-parallel.bash new file mode 100644 index 00000000..b367120a --- /dev/null +++ b/fixtures/sourcehut-parallel.bash @@ -0,0 +1,520 @@ +# SUCCESS +# *INFO* Generating Bash script for testing for GHC versions: 7.8.1 7.8.2 7.8.3 7.8.4 7.10.1 7.10.2 7.10.3 8.0.1 8.0.2 8.2.1 8.2.2 8.4.1 8.4.2 8.4.3 8.4.4 8.6.1 8.6.2 8.6.3 8.6.4 8.6.5 8.8.1 8.8.2 8.8.3 8.8.4 8.10.1 8.10.2 8.10.3 8.10.4 8.10.5 8.10.6 8.10.7 +#!/bin/bash +# shellcheck disable=SC2086,SC2016,SC2046 +# REGENDATA ["--sourcehut-parallel","bash","sourcehut-parallel.project","--sourcehut-source","https://example.org"] + +set -o pipefail + +# Mode +############################################################################## + +if [ "$1" = "indocker" ]; then + INDOCKER=true + shift +else + INDOCKER=false +fi + +# Run configuration +############################################################################## + +CFG_CABAL_STORE_CACHE="" +CFG_CABAL_REPO_CACHE="" +CFG_JOBS="8.10.7 8.10.6 8.10.5 8.10.4 8.10.3 8.10.2 8.10.1 8.8.4 8.8.3 8.8.2 8.8.1 8.6.5 8.6.4 8.6.3 8.6.2 8.6.1 8.4.4 8.4.3 8.4.2 8.4.1 8.2.2 8.2.1 8.0.2 8.0.1 7.10.3 7.10.2 7.10.1 7.8.4 7.8.3 7.8.2 7.8.1" +CFG_CABAL_UPDATE=false + +SCRIPT_NAME=$(basename "$0") +START_TIME="$(date +'%s')" + +XDG_CONFIG_HOME=${XDG_CONFIG_HOME:-$HOME/.config} + +# Job configuration +############################################################################## + +GHC_VERSION="non-existing" +CABAL_VERSION=3.2 +HEADHACKAGE=false + +# Locale +############################################################################## + +export LC_ALL=C.UTF-8 + +# Utilities +############################################################################## + +SGR_RED='\033[1;31m' +SGR_GREEN='\033[1;32m' +SGR_BLUE='\033[1;34m' +SGR_CYAN='\033[1;96m' +SGR_RESET='\033[0m' # No Color + +put_info() { + printf "$SGR_CYAN%s$SGR_RESET\n" "### $*" +} + +put_error() { + printf "$SGR_RED%s$SGR_RESET\n" "!!! $*" +} + +run_cmd() { + local PRETTYCMD="$*" + local PROMPT + if $INDOCKER; then + PROMPT="$(pwd) >>>" + else + PROMPT=">>>" + fi + + printf "$SGR_BLUE%s %s$SGR_RESET\n" "$PROMPT" "$PRETTYCMD" + + local start_time end_time cmd_duration total_duration + start_time=$(date +'%s') + + "$@" + local RET=$? + + end_time=$(date +'%s') + cmd_duration=$((end_time - start_time)) + total_duration=$((end_time - START_TIME)) + + cmd_min=$((cmd_duration / 60)) + cmd_sec=$((cmd_duration % 60)) + + total_min=$((total_duration / 60)) + total_sec=$((total_duration % 60)) + + if [ $RET -eq 0 ]; then + printf "$SGR_GREEN%s$SGR_RESET (%dm%02ds; %dm%02ds)\n" "<<< $PRETTYCMD" "$cmd_min" "$cmd_sec" "$total_min" "$total_sec" + else + printf "$SGR_RED%s$SGR_RESET\n" "!!! $PRETTYCMD" + exit 1 + fi +} + +run_cmd_if() { + local COND=$1 + shift + + if [ $COND -eq 1 ]; then + run_cmd "$@" + else + local PRETTYCMD="$*" + local PROMPT + PROMPT="$(pwd) (skipping) >>>" + + printf "$SGR_BLUE%s %s$SGR_RESET\n" "$PROMPT" "$PRETTYCMD" + fi +} + +run_cmd_unchecked() { + local PRETTYCMD="$*" + local PROMPT + if $INDOCKER; then + PROMPT="$(pwd) >>>" + else + PROMPT=">>>" + fi + + printf "$SGR_BLUE%s %s$SGR_RESET\n" "$PROMPT" "$PRETTYCMD" + + local start_time end_time cmd_duration total_duration cmd_min cmd_sec total_min total_sec + start_time=$(date +'%s') + + "$@" + + end_time=$(date +'%s') + cmd_duration=$((end_time - start_time)) + total_duration=$((end_time - START_TIME)) + + cmd_min=$((cmd_duration / 60)) + cmd_sec=$((cmd_duration % 60)) + + total_min=$((total_duration / 60)) + total_sec=$((total_duration % 60)) + + printf "$SGR_GREEN%s$SGR_RESET (%dm%02ds; %dm%02ds)\n" "<<< $PRETTYCMD" "$cmd_min" "$cmd_sec" "$total_min" "$total_sec" +} + +change_dir() { + local DIR=$1 + if [ -d "$DIR" ]; then + printf "$SGR_BLUE%s$SGR_RESET\n" "change directory to $DIR" + cd "$DIR" || exit 1 + else + printf "$SGR_RED%s$SGR_RESET\n" "!!! cd $DIR" + exit 1 + fi +} + +change_dir_if() { + local COND=$1 + local DIR=$2 + + if [ $COND -ne 0 ]; then + change_dir "$DIR" + fi +} + +echo_to() { + local DEST=$1 + local CONTENTS=$2 + + echo "$CONTENTS" >> "$DEST" +} + +echo_if_to() { + local COND=$1 + local DEST=$2 + local CONTENTS=$3 + + if [ $COND -ne 0 ]; then + echo_to "$DEST" "$CONTENTS" + fi +} + +install_cabalplan() { + put_info "installing cabal-plan" + + if [ ! -e $CABAL_REPOCACHE/downloads/cabal-plan ]; then + curl -L https://github.com/haskell-hvr/cabal-plan/releases/download/v0.6.2.0/cabal-plan-0.6.2.0-x86_64-linux.xz > /tmp/cabal-plan.xz || exit 1 + (cd /tmp && echo "de73600b1836d3f55e32d80385acc055fd97f60eaa0ab68a755302685f5d81bc cabal-plan.xz" | sha256sum -c -)|| exit 1 + mkdir -p $CABAL_REPOCACHE/downloads + xz -d < /tmp/cabal-plan.xz > $CABAL_REPOCACHE/downloads/cabal-plan || exit 1 + chmod a+x $CABAL_REPOCACHE/downloads/cabal-plan || exit 1 + fi + + mkdir -p $CABAL_DIR/bin || exit 1 + ln -s $CABAL_REPOCACHE/downloads/cabal-plan $CABAL_DIR/bin/cabal-plan || exit 1 +} + +# Help +############################################################################## + +show_usage() { +cat < $BUILDDIR/cabal/config <= 80200)) cabal.project "package servant" +echo_if_to $((HCNUMVER >= 80200)) cabal.project " ghc-options: -Werror=missing-methods" +cat >> cabal.project <> cabal.project.local +run_cmd cat cabal.project +run_cmd cat cabal.project.local + +# dump install plan +put_info "dump install plan" +run_cmd $CABAL v2-build $ARG_COMPILER $ARG_TESTS $ARG_BENCH --dry-run all +run_cmd cabal-plan + +# install dependencies +put_info "install dependencies" +run_cmd $CABAL v2-build $ARG_COMPILER --disable-tests --disable-benchmarks --dependencies-only -j all +run_cmd $CABAL v2-build $ARG_COMPILER $ARG_TESTS $ARG_BENCH --dependencies-only -j all + +# build w/o tests +put_info "build w/o tests" +run_cmd $CABAL v2-build $ARG_COMPILER --disable-tests --disable-benchmarks all + +# build +put_info "build" +run_cmd $CABAL v2-build $ARG_COMPILER $ARG_TESTS $ARG_BENCH all + +# tests +put_info "tests" +run_cmd $CABAL v2-test $ARG_COMPILER $ARG_TESTS $ARG_BENCH all --test-show-details=direct + +# cabal check +put_info "cabal check" +change_dir "${PKGDIR_servant}" +run_cmd ${CABAL} -vnormal check +change_dir "$BUILDDIR" + +# haddock +put_info "haddock" +run_cmd $CABAL v2-haddock $ARG_COMPILER --with-haddock $HADDOCK $ARG_TESTS $ARG_BENCH all + +# unconstrained build +put_info "unconstrained build" +run_cmd rm -f cabal.project.local +run_cmd $CABAL v2-build $ARG_COMPILER --disable-tests --disable-benchmarks all + + +# Done +run_cmd echo OK diff --git a/fixtures/sourcehut-parallel.github b/fixtures/sourcehut-parallel.github new file mode 100644 index 00000000..eba63cae --- /dev/null +++ b/fixtures/sourcehut-parallel.github @@ -0,0 +1,352 @@ +# SUCCESS +# *INFO* Generating GitHub config for testing for GHC versions: 7.8.1 7.8.2 7.8.3 7.8.4 7.10.1 7.10.2 7.10.3 8.0.1 8.0.2 8.2.1 8.2.2 8.4.1 8.4.2 8.4.3 8.4.4 8.6.1 8.6.2 8.6.3 8.6.4 8.6.5 8.8.1 8.8.2 8.8.3 8.8.4 8.10.1 8.10.2 8.10.3 8.10.4 8.10.5 8.10.6 8.10.7 +# This GitHub workflow config has been generated by a script via +# +# haskell-ci '--sourcehut-parallel' 'github' 'sourcehut-parallel.project' '--sourcehut-source' 'https://example.org' +# +# 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 +# +# REGENDATA ["--sourcehut-parallel","github","sourcehut-parallel.project","--sourcehut-source","https://example.org"] +# +name: Haskell-CI +on: + - push + - pull_request +jobs: + linux: + name: Haskell-CI - Linux - ${{ matrix.compiler }} + runs-on: ubuntu-18.04 + timeout-minutes: + 60 + container: + image: buildpack-deps:bionic + continue-on-error: ${{ matrix.allow-failure }} + strategy: + matrix: + include: + - compiler: ghc-8.10.7 + compilerKind: ghc + compilerVersion: 8.10.7 + setup-method: ghcup + allow-failure: false + - compiler: ghc-8.10.6 + compilerKind: ghc + compilerVersion: 8.10.6 + setup-method: ghcup + allow-failure: false + - compiler: ghc-8.10.5 + compilerKind: ghc + compilerVersion: 8.10.5 + setup-method: ghcup + allow-failure: false + - compiler: ghc-8.10.4 + compilerKind: ghc + compilerVersion: 8.10.4 + setup-method: hvr-ppa + allow-failure: false + - compiler: ghc-8.10.3 + compilerKind: ghc + compilerVersion: 8.10.3 + setup-method: hvr-ppa + allow-failure: false + - compiler: ghc-8.10.2 + compilerKind: ghc + compilerVersion: 8.10.2 + setup-method: hvr-ppa + allow-failure: false + - compiler: ghc-8.10.1 + compilerKind: ghc + compilerVersion: 8.10.1 + setup-method: hvr-ppa + allow-failure: false + - compiler: ghc-8.8.4 + compilerKind: ghc + compilerVersion: 8.8.4 + setup-method: hvr-ppa + allow-failure: false + - compiler: ghc-8.8.3 + compilerKind: ghc + compilerVersion: 8.8.3 + setup-method: hvr-ppa + allow-failure: false + - compiler: ghc-8.8.2 + compilerKind: ghc + compilerVersion: 8.8.2 + setup-method: hvr-ppa + allow-failure: false + - compiler: ghc-8.8.1 + compilerKind: ghc + compilerVersion: 8.8.1 + setup-method: hvr-ppa + allow-failure: false + - compiler: ghc-8.6.5 + compilerKind: ghc + compilerVersion: 8.6.5 + setup-method: hvr-ppa + allow-failure: false + - compiler: ghc-8.6.4 + compilerKind: ghc + compilerVersion: 8.6.4 + setup-method: hvr-ppa + allow-failure: false + - compiler: ghc-8.6.3 + compilerKind: ghc + compilerVersion: 8.6.3 + setup-method: hvr-ppa + allow-failure: false + - compiler: ghc-8.6.2 + compilerKind: ghc + compilerVersion: 8.6.2 + setup-method: hvr-ppa + allow-failure: false + - compiler: ghc-8.6.1 + compilerKind: ghc + compilerVersion: 8.6.1 + setup-method: hvr-ppa + allow-failure: false + - compiler: ghc-8.4.4 + compilerKind: ghc + compilerVersion: 8.4.4 + setup-method: hvr-ppa + allow-failure: false + - compiler: ghc-8.4.3 + compilerKind: ghc + compilerVersion: 8.4.3 + setup-method: hvr-ppa + allow-failure: false + - compiler: ghc-8.4.2 + compilerKind: ghc + compilerVersion: 8.4.2 + setup-method: hvr-ppa + allow-failure: false + - compiler: ghc-8.4.1 + compilerKind: ghc + compilerVersion: 8.4.1 + setup-method: hvr-ppa + allow-failure: false + - compiler: ghc-8.2.2 + compilerKind: ghc + compilerVersion: 8.2.2 + setup-method: hvr-ppa + allow-failure: false + - compiler: ghc-8.2.1 + compilerKind: ghc + compilerVersion: 8.2.1 + setup-method: hvr-ppa + allow-failure: false + - compiler: ghc-8.0.2 + compilerKind: ghc + compilerVersion: 8.0.2 + setup-method: hvr-ppa + allow-failure: false + - compiler: ghc-8.0.1 + compilerKind: ghc + compilerVersion: 8.0.1 + setup-method: hvr-ppa + allow-failure: false + - compiler: ghc-7.10.3 + compilerKind: ghc + compilerVersion: 7.10.3 + setup-method: hvr-ppa + allow-failure: false + - compiler: ghc-7.10.2 + compilerKind: ghc + compilerVersion: 7.10.2 + setup-method: hvr-ppa + allow-failure: false + - compiler: ghc-7.10.1 + compilerKind: ghc + compilerVersion: 7.10.1 + setup-method: hvr-ppa + allow-failure: false + - compiler: ghc-7.8.4 + compilerKind: ghc + compilerVersion: 7.8.4 + setup-method: hvr-ppa + allow-failure: false + - compiler: ghc-7.8.3 + compilerKind: ghc + compilerVersion: 7.8.3 + setup-method: hvr-ppa + allow-failure: false + - compiler: ghc-7.8.2 + compilerKind: ghc + compilerVersion: 7.8.2 + setup-method: hvr-ppa + allow-failure: false + - compiler: ghc-7.8.1 + compilerKind: ghc + compilerVersion: 7.8.1 + setup-method: hvr-ppa + allow-failure: false + fail-fast: false + steps: + - name: apt + run: | + apt-get update + apt-get install -y --no-install-recommends gnupg ca-certificates dirmngr curl git software-properties-common libtinfo5 + if [ "${{ matrix.setup-method }}" = ghcup ]; then + mkdir -p "$HOME/.ghcup/bin" + curl -sL https://downloads.haskell.org/ghcup/0.1.17.3/x86_64-linux-ghcup-0.1.17.3 > "$HOME/.ghcup/bin/ghcup" + chmod a+x "$HOME/.ghcup/bin/ghcup" + "$HOME/.ghcup/bin/ghcup" install ghc "$HCVER" + "$HOME/.ghcup/bin/ghcup" install cabal 3.6.2.0 + else + apt-add-repository -y 'ppa:hvr/ghc' + apt-get update + apt-get install -y "$HCNAME" + mkdir -p "$HOME/.ghcup/bin" + curl -sL https://downloads.haskell.org/ghcup/0.1.17.3/x86_64-linux-ghcup-0.1.17.3 > "$HOME/.ghcup/bin/ghcup" + chmod a+x "$HOME/.ghcup/bin/ghcup" + "$HOME/.ghcup/bin/ghcup" install cabal 3.6.2.0 + fi + env: + HCKIND: ${{ matrix.compilerKind }} + HCNAME: ${{ matrix.compiler }} + HCVER: ${{ matrix.compilerVersion }} + - name: Set PATH and environment variables + run: | + echo "$HOME/.cabal/bin" >> $GITHUB_PATH + echo "LANG=C.UTF-8" >> "$GITHUB_ENV" + echo "CABAL_DIR=$HOME/.cabal" >> "$GITHUB_ENV" + echo "CABAL_CONFIG=$HOME/.cabal/config" >> "$GITHUB_ENV" + HCDIR=/opt/$HCKIND/$HCVER + if [ "${{ matrix.setup-method }}" = ghcup ]; then + HC=$HOME/.ghcup/bin/$HCKIND-$HCVER + echo "HC=$HC" >> "$GITHUB_ENV" + echo "HCPKG=$HOME/.ghcup/bin/$HCKIND-pkg-$HCVER" >> "$GITHUB_ENV" + echo "HADDOCK=$HOME/.ghcup/bin/haddock-$HCVER" >> "$GITHUB_ENV" + echo "CABAL=$HOME/.ghcup/bin/cabal-3.6.2.0 -vnormal+nowrap" >> "$GITHUB_ENV" + else + HC=$HCDIR/bin/$HCKIND + echo "HC=$HC" >> "$GITHUB_ENV" + echo "HCPKG=$HCDIR/bin/$HCKIND-pkg" >> "$GITHUB_ENV" + echo "HADDOCK=$HCDIR/bin/haddock" >> "$GITHUB_ENV" + echo "CABAL=$HOME/.ghcup/bin/cabal-3.6.2.0 -vnormal+nowrap" >> "$GITHUB_ENV" + fi + + HCNUMVER=$(${HC} --numeric-version|perl -ne '/^(\d+)\.(\d+)\.(\d+)(\.(\d+))?$/; print(10000 * $1 + 100 * $2 + ($3 == 0 ? $5 != 1 : $3))') + echo "HCNUMVER=$HCNUMVER" >> "$GITHUB_ENV" + echo "ARG_TESTS=--enable-tests" >> "$GITHUB_ENV" + echo "ARG_BENCH=--enable-benchmarks" >> "$GITHUB_ENV" + echo "HEADHACKAGE=false" >> "$GITHUB_ENV" + echo "ARG_COMPILER=--$HCKIND --with-compiler=$HC" >> "$GITHUB_ENV" + echo "GHCJSARITH=0" >> "$GITHUB_ENV" + env: + HCKIND: ${{ matrix.compilerKind }} + HCNAME: ${{ matrix.compiler }} + HCVER: ${{ matrix.compilerVersion }} + - name: env + run: | + env + - name: write cabal config + run: | + mkdir -p $CABAL_DIR + cat >> $CABAL_CONFIG <> $CABAL_CONFIG < cabal-plan.xz + echo 'de73600b1836d3f55e32d80385acc055fd97f60eaa0ab68a755302685f5d81bc cabal-plan.xz' | sha256sum -c - + xz -d < cabal-plan.xz > $HOME/.cabal/bin/cabal-plan + rm -f cabal-plan.xz + chmod a+x $HOME/.cabal/bin/cabal-plan + cabal-plan --version + - name: checkout + uses: actions/checkout@v2 + with: + path: source + - name: initial cabal.project for sdist + run: | + touch cabal.project + echo "packages: $GITHUB_WORKSPACE/source/servant" >> cabal.project + cat cabal.project + - name: sdist + run: | + mkdir -p sdist + $CABAL sdist all --output-dir $GITHUB_WORKSPACE/sdist + - name: unpack + run: | + mkdir -p unpacked + find sdist -maxdepth 1 -type f -name '*.tar.gz' -exec tar -C $GITHUB_WORKSPACE/unpacked -xzvf {} \; + - name: generate cabal.project + run: | + PKGDIR_servant="$(find "$GITHUB_WORKSPACE/unpacked" -maxdepth 1 -type d -regex '.*/servant-[0-9.]*')" + echo "PKGDIR_servant=${PKGDIR_servant}" >> "$GITHUB_ENV" + rm -f cabal.project cabal.project.local + touch cabal.project + touch cabal.project.local + echo "packages: ${PKGDIR_servant}" >> cabal.project + if [ $((HCNUMVER >= 80200)) -ne 0 ] ; then echo "package servant" >> cabal.project ; fi + if [ $((HCNUMVER >= 80200)) -ne 0 ] ; then echo " ghc-options: -Werror=missing-methods" >> cabal.project ; fi + cat >> cabal.project <> cabal.project.local + cat cabal.project + cat cabal.project.local + - name: dump install plan + run: | + $CABAL v2-build $ARG_COMPILER $ARG_TESTS $ARG_BENCH --dry-run all + cabal-plan + - name: cache + uses: actions/cache@v2 + with: + key: ${{ runner.os }}-${{ matrix.compiler }}-${{ github.sha }} + path: ~/.cabal/store + restore-keys: ${{ runner.os }}-${{ matrix.compiler }}- + - name: install dependencies + run: | + $CABAL v2-build $ARG_COMPILER --disable-tests --disable-benchmarks --dependencies-only -j2 all + $CABAL v2-build $ARG_COMPILER $ARG_TESTS $ARG_BENCH --dependencies-only -j2 all + - name: build w/o tests + run: | + $CABAL v2-build $ARG_COMPILER --disable-tests --disable-benchmarks all + - name: build + run: | + $CABAL v2-build $ARG_COMPILER $ARG_TESTS $ARG_BENCH all --write-ghc-environment-files=always + - name: tests + run: | + $CABAL v2-test $ARG_COMPILER $ARG_TESTS $ARG_BENCH all --test-show-details=direct + - name: cabal check + run: | + cd ${PKGDIR_servant} || false + ${CABAL} -vnormal check + - name: haddock + run: | + $CABAL v2-haddock $ARG_COMPILER --with-haddock $HADDOCK $ARG_TESTS $ARG_BENCH all + - name: unconstrained build + run: | + rm -f cabal.project.local + $CABAL v2-build $ARG_COMPILER --disable-tests --disable-benchmarks all diff --git a/fixtures/sourcehut-parallel.project b/fixtures/sourcehut-parallel.project new file mode 100644 index 00000000..9fc81673 --- /dev/null +++ b/fixtures/sourcehut-parallel.project @@ -0,0 +1 @@ +packages: servant diff --git a/fixtures/sourcehut-parallel.sourcehut b/fixtures/sourcehut-parallel.sourcehut new file mode 100644 index 00000000..ee3b4eaa --- /dev/null +++ b/fixtures/sourcehut-parallel.sourcehut @@ -0,0 +1,1552 @@ +# SUCCESS +# *INFO* Generating Sourcehut config for testing for GHC versions: 7.8.1 7.8.2 7.8.3 7.8.4 7.10.1 7.10.2 7.10.3 8.0.1 8.0.2 8.2.1 8.2.2 8.4.1 8.4.2 8.4.3 8.4.4 8.6.1 8.6.2 8.6.3 8.6.4 8.6.5 8.8.1 8.8.2 8.8.3 8.8.4 8.10.1 8.10.2 8.10.3 8.10.4 8.10.5 8.10.6 8.10.7 +# manifest name: 7.10.1 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--sourcehut-parallel' 'sourcehut' 'sourcehut-parallel.project' '--sourcehut-source' 'https://example.org' +# +# 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 +# +# REGENDATA ["--sourcehut-parallel","sourcehut","sourcehut-parallel.project","--sourcehut-source","https://example.org"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-7.10.1 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 7_10_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.10.1 + - 7_10_1-check: | + cd example.org + cabal check + - 7_10_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_10_1-build: | + cd example.org + cabal build all + - 7_10_1-test: | + cd example.org + cabal test all --enable-tests + - 7_10_1-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 7.10.2 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--sourcehut-parallel' 'sourcehut' 'sourcehut-parallel.project' '--sourcehut-source' 'https://example.org' +# +# 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 +# +# REGENDATA ["--sourcehut-parallel","sourcehut","sourcehut-parallel.project","--sourcehut-source","https://example.org"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-7.10.2 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 7_10_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.10.2 + - 7_10_2-check: | + cd example.org + cabal check + - 7_10_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_10_2-build: | + cd example.org + cabal build all + - 7_10_2-test: | + cd example.org + cabal test all --enable-tests + - 7_10_2-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 7.10.3 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--sourcehut-parallel' 'sourcehut' 'sourcehut-parallel.project' '--sourcehut-source' 'https://example.org' +# +# 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 +# +# REGENDATA ["--sourcehut-parallel","sourcehut","sourcehut-parallel.project","--sourcehut-source","https://example.org"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-7.10.3 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 7_10_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.10.3 + - 7_10_3-check: | + cd example.org + cabal check + - 7_10_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_10_3-build: | + cd example.org + cabal build all + - 7_10_3-test: | + cd example.org + cabal test all --enable-tests + - 7_10_3-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 7.8.1 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--sourcehut-parallel' 'sourcehut' 'sourcehut-parallel.project' '--sourcehut-source' 'https://example.org' +# +# 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 +# +# REGENDATA ["--sourcehut-parallel","sourcehut","sourcehut-parallel.project","--sourcehut-source","https://example.org"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-7.8.1 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 7_8_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.8.1 + - 7_8_1-check: | + cd example.org + cabal check + - 7_8_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_8_1-build: | + cd example.org + cabal build all + - 7_8_1-test: | + cd example.org + cabal test all --enable-tests + - 7_8_1-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 7.8.2 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--sourcehut-parallel' 'sourcehut' 'sourcehut-parallel.project' '--sourcehut-source' 'https://example.org' +# +# 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 +# +# REGENDATA ["--sourcehut-parallel","sourcehut","sourcehut-parallel.project","--sourcehut-source","https://example.org"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-7.8.2 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 7_8_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.8.2 + - 7_8_2-check: | + cd example.org + cabal check + - 7_8_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_8_2-build: | + cd example.org + cabal build all + - 7_8_2-test: | + cd example.org + cabal test all --enable-tests + - 7_8_2-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 7.8.3 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--sourcehut-parallel' 'sourcehut' 'sourcehut-parallel.project' '--sourcehut-source' 'https://example.org' +# +# 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 +# +# REGENDATA ["--sourcehut-parallel","sourcehut","sourcehut-parallel.project","--sourcehut-source","https://example.org"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-7.8.3 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 7_8_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.8.3 + - 7_8_3-check: | + cd example.org + cabal check + - 7_8_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_8_3-build: | + cd example.org + cabal build all + - 7_8_3-test: | + cd example.org + cabal test all --enable-tests + - 7_8_3-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 7.8.4 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--sourcehut-parallel' 'sourcehut' 'sourcehut-parallel.project' '--sourcehut-source' 'https://example.org' +# +# 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 +# +# REGENDATA ["--sourcehut-parallel","sourcehut","sourcehut-parallel.project","--sourcehut-source","https://example.org"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-7.8.4 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 7_8_4-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-7.8.4 + - 7_8_4-check: | + cd example.org + cabal check + - 7_8_4-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 7_8_4-build: | + cd example.org + cabal build all + - 7_8_4-test: | + cd example.org + cabal test all --enable-tests + - 7_8_4-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.0.1 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--sourcehut-parallel' 'sourcehut' 'sourcehut-parallel.project' '--sourcehut-source' 'https://example.org' +# +# 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 +# +# REGENDATA ["--sourcehut-parallel","sourcehut","sourcehut-parallel.project","--sourcehut-source","https://example.org"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.0.1 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_0_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.0.1 + - 8_0_1-check: | + cd example.org + cabal check + - 8_0_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_0_1-build: | + cd example.org + cabal build all + - 8_0_1-test: | + cd example.org + cabal test all --enable-tests + - 8_0_1-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.0.2 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--sourcehut-parallel' 'sourcehut' 'sourcehut-parallel.project' '--sourcehut-source' 'https://example.org' +# +# 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 +# +# REGENDATA ["--sourcehut-parallel","sourcehut","sourcehut-parallel.project","--sourcehut-source","https://example.org"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.0.2 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_0_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.0.2 + - 8_0_2-check: | + cd example.org + cabal check + - 8_0_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_0_2-build: | + cd example.org + cabal build all + - 8_0_2-test: | + cd example.org + cabal test all --enable-tests + - 8_0_2-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.10.1 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--sourcehut-parallel' 'sourcehut' 'sourcehut-parallel.project' '--sourcehut-source' 'https://example.org' +# +# 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 +# +# REGENDATA ["--sourcehut-parallel","sourcehut","sourcehut-parallel.project","--sourcehut-source","https://example.org"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.10.1 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_10_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.1 + - 8_10_1-check: | + cd example.org + cabal check + - 8_10_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_1-build: | + cd example.org + cabal build all + - 8_10_1-test: | + cd example.org + cabal test all --enable-tests + - 8_10_1-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.10.2 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--sourcehut-parallel' 'sourcehut' 'sourcehut-parallel.project' '--sourcehut-source' 'https://example.org' +# +# 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 +# +# REGENDATA ["--sourcehut-parallel","sourcehut","sourcehut-parallel.project","--sourcehut-source","https://example.org"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.10.2 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_10_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.2 + - 8_10_2-check: | + cd example.org + cabal check + - 8_10_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_2-build: | + cd example.org + cabal build all + - 8_10_2-test: | + cd example.org + cabal test all --enable-tests + - 8_10_2-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.10.3 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--sourcehut-parallel' 'sourcehut' 'sourcehut-parallel.project' '--sourcehut-source' 'https://example.org' +# +# 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 +# +# REGENDATA ["--sourcehut-parallel","sourcehut","sourcehut-parallel.project","--sourcehut-source","https://example.org"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.10.3 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_10_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.3 + - 8_10_3-check: | + cd example.org + cabal check + - 8_10_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_3-build: | + cd example.org + cabal build all + - 8_10_3-test: | + cd example.org + cabal test all --enable-tests + - 8_10_3-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.10.4 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--sourcehut-parallel' 'sourcehut' 'sourcehut-parallel.project' '--sourcehut-source' 'https://example.org' +# +# 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 +# +# REGENDATA ["--sourcehut-parallel","sourcehut","sourcehut-parallel.project","--sourcehut-source","https://example.org"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.10.4 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_10_4-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.4 + - 8_10_4-check: | + cd example.org + cabal check + - 8_10_4-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_4-build: | + cd example.org + cabal build all + - 8_10_4-test: | + cd example.org + cabal test all --enable-tests + - 8_10_4-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.10.5 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--sourcehut-parallel' 'sourcehut' 'sourcehut-parallel.project' '--sourcehut-source' 'https://example.org' +# +# 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 +# +# REGENDATA ["--sourcehut-parallel","sourcehut","sourcehut-parallel.project","--sourcehut-source","https://example.org"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.10.5 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_10_5-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.5 + - 8_10_5-check: | + cd example.org + cabal check + - 8_10_5-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_5-build: | + cd example.org + cabal build all + - 8_10_5-test: | + cd example.org + cabal test all --enable-tests + - 8_10_5-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.10.6 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--sourcehut-parallel' 'sourcehut' 'sourcehut-parallel.project' '--sourcehut-source' 'https://example.org' +# +# 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 +# +# REGENDATA ["--sourcehut-parallel","sourcehut","sourcehut-parallel.project","--sourcehut-source","https://example.org"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.10.6 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_10_6-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.6 + - 8_10_6-check: | + cd example.org + cabal check + - 8_10_6-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_6-build: | + cd example.org + cabal build all + - 8_10_6-test: | + cd example.org + cabal test all --enable-tests + - 8_10_6-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.10.7 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--sourcehut-parallel' 'sourcehut' 'sourcehut-parallel.project' '--sourcehut-source' 'https://example.org' +# +# 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 +# +# REGENDATA ["--sourcehut-parallel","sourcehut","sourcehut-parallel.project","--sourcehut-source","https://example.org"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.10.7 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_10_7-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.10.7 + - 8_10_7-check: | + cd example.org + cabal check + - 8_10_7-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_10_7-build: | + cd example.org + cabal build all + - 8_10_7-test: | + cd example.org + cabal test all --enable-tests + - 8_10_7-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.2.1 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--sourcehut-parallel' 'sourcehut' 'sourcehut-parallel.project' '--sourcehut-source' 'https://example.org' +# +# 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 +# +# REGENDATA ["--sourcehut-parallel","sourcehut","sourcehut-parallel.project","--sourcehut-source","https://example.org"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.2.1 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_2_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.2.1 + - 8_2_1-check: | + cd example.org + cabal check + - 8_2_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_2_1-build: | + cd example.org + cabal build all + - 8_2_1-test: | + cd example.org + cabal test all --enable-tests + - 8_2_1-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.2.2 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--sourcehut-parallel' 'sourcehut' 'sourcehut-parallel.project' '--sourcehut-source' 'https://example.org' +# +# 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 +# +# REGENDATA ["--sourcehut-parallel","sourcehut","sourcehut-parallel.project","--sourcehut-source","https://example.org"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.2.2 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_2_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.2.2 + - 8_2_2-check: | + cd example.org + cabal check + - 8_2_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_2_2-build: | + cd example.org + cabal build all + - 8_2_2-test: | + cd example.org + cabal test all --enable-tests + - 8_2_2-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.4.1 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--sourcehut-parallel' 'sourcehut' 'sourcehut-parallel.project' '--sourcehut-source' 'https://example.org' +# +# 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 +# +# REGENDATA ["--sourcehut-parallel","sourcehut","sourcehut-parallel.project","--sourcehut-source","https://example.org"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.4.1 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_4_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.4.1 + - 8_4_1-check: | + cd example.org + cabal check + - 8_4_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_4_1-build: | + cd example.org + cabal build all + - 8_4_1-test: | + cd example.org + cabal test all --enable-tests + - 8_4_1-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.4.2 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--sourcehut-parallel' 'sourcehut' 'sourcehut-parallel.project' '--sourcehut-source' 'https://example.org' +# +# 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 +# +# REGENDATA ["--sourcehut-parallel","sourcehut","sourcehut-parallel.project","--sourcehut-source","https://example.org"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.4.2 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_4_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.4.2 + - 8_4_2-check: | + cd example.org + cabal check + - 8_4_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_4_2-build: | + cd example.org + cabal build all + - 8_4_2-test: | + cd example.org + cabal test all --enable-tests + - 8_4_2-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.4.3 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--sourcehut-parallel' 'sourcehut' 'sourcehut-parallel.project' '--sourcehut-source' 'https://example.org' +# +# 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 +# +# REGENDATA ["--sourcehut-parallel","sourcehut","sourcehut-parallel.project","--sourcehut-source","https://example.org"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.4.3 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_4_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.4.3 + - 8_4_3-check: | + cd example.org + cabal check + - 8_4_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_4_3-build: | + cd example.org + cabal build all + - 8_4_3-test: | + cd example.org + cabal test all --enable-tests + - 8_4_3-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.4.4 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--sourcehut-parallel' 'sourcehut' 'sourcehut-parallel.project' '--sourcehut-source' 'https://example.org' +# +# 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 +# +# REGENDATA ["--sourcehut-parallel","sourcehut","sourcehut-parallel.project","--sourcehut-source","https://example.org"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.4.4 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_4_4-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.4.4 + - 8_4_4-check: | + cd example.org + cabal check + - 8_4_4-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_4_4-build: | + cd example.org + cabal build all + - 8_4_4-test: | + cd example.org + cabal test all --enable-tests + - 8_4_4-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.6.1 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--sourcehut-parallel' 'sourcehut' 'sourcehut-parallel.project' '--sourcehut-source' 'https://example.org' +# +# 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 +# +# REGENDATA ["--sourcehut-parallel","sourcehut","sourcehut-parallel.project","--sourcehut-source","https://example.org"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.6.1 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_6_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.6.1 + - 8_6_1-check: | + cd example.org + cabal check + - 8_6_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_6_1-build: | + cd example.org + cabal build all + - 8_6_1-test: | + cd example.org + cabal test all --enable-tests + - 8_6_1-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.6.2 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--sourcehut-parallel' 'sourcehut' 'sourcehut-parallel.project' '--sourcehut-source' 'https://example.org' +# +# 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 +# +# REGENDATA ["--sourcehut-parallel","sourcehut","sourcehut-parallel.project","--sourcehut-source","https://example.org"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.6.2 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_6_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.6.2 + - 8_6_2-check: | + cd example.org + cabal check + - 8_6_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_6_2-build: | + cd example.org + cabal build all + - 8_6_2-test: | + cd example.org + cabal test all --enable-tests + - 8_6_2-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.6.3 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--sourcehut-parallel' 'sourcehut' 'sourcehut-parallel.project' '--sourcehut-source' 'https://example.org' +# +# 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 +# +# REGENDATA ["--sourcehut-parallel","sourcehut","sourcehut-parallel.project","--sourcehut-source","https://example.org"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.6.3 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_6_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.6.3 + - 8_6_3-check: | + cd example.org + cabal check + - 8_6_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_6_3-build: | + cd example.org + cabal build all + - 8_6_3-test: | + cd example.org + cabal test all --enable-tests + - 8_6_3-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.6.4 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--sourcehut-parallel' 'sourcehut' 'sourcehut-parallel.project' '--sourcehut-source' 'https://example.org' +# +# 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 +# +# REGENDATA ["--sourcehut-parallel","sourcehut","sourcehut-parallel.project","--sourcehut-source","https://example.org"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.6.4 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_6_4-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.6.4 + - 8_6_4-check: | + cd example.org + cabal check + - 8_6_4-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_6_4-build: | + cd example.org + cabal build all + - 8_6_4-test: | + cd example.org + cabal test all --enable-tests + - 8_6_4-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.6.5 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--sourcehut-parallel' 'sourcehut' 'sourcehut-parallel.project' '--sourcehut-source' 'https://example.org' +# +# 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 +# +# REGENDATA ["--sourcehut-parallel","sourcehut","sourcehut-parallel.project","--sourcehut-source","https://example.org"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.6.5 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_6_5-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.6.5 + - 8_6_5-check: | + cd example.org + cabal check + - 8_6_5-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_6_5-build: | + cd example.org + cabal build all + - 8_6_5-test: | + cd example.org + cabal test all --enable-tests + - 8_6_5-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.8.1 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--sourcehut-parallel' 'sourcehut' 'sourcehut-parallel.project' '--sourcehut-source' 'https://example.org' +# +# 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 +# +# REGENDATA ["--sourcehut-parallel","sourcehut","sourcehut-parallel.project","--sourcehut-source","https://example.org"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.8.1 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_8_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.8.1 + - 8_8_1-check: | + cd example.org + cabal check + - 8_8_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_8_1-build: | + cd example.org + cabal build all + - 8_8_1-test: | + cd example.org + cabal test all --enable-tests + - 8_8_1-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.8.2 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--sourcehut-parallel' 'sourcehut' 'sourcehut-parallel.project' '--sourcehut-source' 'https://example.org' +# +# 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 +# +# REGENDATA ["--sourcehut-parallel","sourcehut","sourcehut-parallel.project","--sourcehut-source","https://example.org"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.8.2 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_8_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.8.2 + - 8_8_2-check: | + cd example.org + cabal check + - 8_8_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_8_2-build: | + cd example.org + cabal build all + - 8_8_2-test: | + cd example.org + cabal test all --enable-tests + - 8_8_2-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.8.3 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--sourcehut-parallel' 'sourcehut' 'sourcehut-parallel.project' '--sourcehut-source' 'https://example.org' +# +# 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 +# +# REGENDATA ["--sourcehut-parallel","sourcehut","sourcehut-parallel.project","--sourcehut-source","https://example.org"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.8.3 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_8_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.8.3 + - 8_8_3-check: | + cd example.org + cabal check + - 8_8_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_8_3-build: | + cd example.org + cabal build all + - 8_8_3-test: | + cd example.org + cabal test all --enable-tests + - 8_8_3-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com +# manifest name: 8.8.4 +# This Sourcehut job script has been generated by a script via +# +# haskell-ci '--sourcehut-parallel' 'sourcehut' 'sourcehut-parallel.project' '--sourcehut-source' 'https://example.org' +# +# 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 +# +# REGENDATA ["--sourcehut-parallel","sourcehut","sourcehut-parallel.project","--sourcehut-source","https://example.org"] +# +image: ubuntu/bionic +packages: + - gcc + - cabal-install-3.4 + - ghc-8.8.4 +repositories: + hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 +sources: + - https://example.org +tasks: + - all-prepare: | + export PATH=$PATH:/opt/cabal/bin + echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + cabal update + - 8_8_4-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-8.8.4 + - 8_8_4-check: | + cd example.org + cabal check + - 8_8_4-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 8_8_4-build: | + cd example.org + cabal build all + - 8_8_4-test: | + cd example.org + cabal test all --enable-tests + - 8_8_4-haddock: | + cd example.org + cabal haddock all +triggers: + - action: email + condition: failure + to: haskell-servant-maintainers@googlegroups.com diff --git a/fixtures/sourcehut-parallel.travis b/fixtures/sourcehut-parallel.travis new file mode 100644 index 00000000..1e4f25e6 --- /dev/null +++ b/fixtures/sourcehut-parallel.travis @@ -0,0 +1,227 @@ +# SUCCESS +# *INFO* Generating Travis-CI config for testing for GHC versions: 7.8.1 7.8.2 7.8.3 7.8.4 7.10.1 7.10.2 7.10.3 8.0.1 8.0.2 8.2.1 8.2.2 8.4.1 8.4.2 8.4.3 8.4.4 8.6.1 8.6.2 8.6.3 8.6.4 8.6.5 8.8.1 8.8.2 8.8.3 8.8.4 8.10.1 8.10.2 8.10.3 8.10.4 8.10.5 8.10.6 8.10.7 +# This Travis job script has been generated by a script via +# +# haskell-ci '--sourcehut-parallel' 'travis' 'sourcehut-parallel.project' '--sourcehut-source' 'https://example.org' +# +# 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 +# +version: ~> 1.0 +language: c +os: linux +dist: bionic +git: + # whether to recursively clone submodules + submodules: false +cache: + directories: + - $HOME/.cabal/packages + - $HOME/.cabal/store + - $HOME/.hlint +before_cache: + - rm -fv $CABALHOME/packages/hackage.haskell.org/build-reports.log + # remove files that are regenerated by 'cabal update' + - rm -fv $CABALHOME/packages/hackage.haskell.org/00-index.* + - rm -fv $CABALHOME/packages/hackage.haskell.org/*.json + - rm -fv $CABALHOME/packages/hackage.haskell.org/01-index.cache + - rm -fv $CABALHOME/packages/hackage.haskell.org/01-index.tar + - rm -fv $CABALHOME/packages/hackage.haskell.org/01-index.tar.idx + - rm -rfv $CABALHOME/packages/head.hackage +jobs: + include: + - compiler: ghc-8.10.7 + addons: {"apt":{"packages":["ghc-8.10.7","cabal-install-3.6"],"sources":[{"key_url":"https://keyserver.ubuntu.com/pks/lookup?op=get&search=0x063dab2bdc0b3f9fcebc378bff3aeacef6f88286","sourceline":"deb http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main"}]}} + os: linux + - compiler: ghc-8.10.6 + addons: {"apt":{"packages":["ghc-8.10.6","cabal-install-3.6"],"sources":[{"key_url":"https://keyserver.ubuntu.com/pks/lookup?op=get&search=0x063dab2bdc0b3f9fcebc378bff3aeacef6f88286","sourceline":"deb http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main"}]}} + os: linux + - compiler: ghc-8.10.5 + addons: {"apt":{"packages":["ghc-8.10.5","cabal-install-3.6"],"sources":[{"key_url":"https://keyserver.ubuntu.com/pks/lookup?op=get&search=0x063dab2bdc0b3f9fcebc378bff3aeacef6f88286","sourceline":"deb http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main"}]}} + os: linux + - compiler: ghc-8.10.4 + addons: {"apt":{"packages":["ghc-8.10.4","cabal-install-3.6"],"sources":[{"key_url":"https://keyserver.ubuntu.com/pks/lookup?op=get&search=0x063dab2bdc0b3f9fcebc378bff3aeacef6f88286","sourceline":"deb http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main"}]}} + os: linux + - compiler: ghc-8.10.3 + addons: {"apt":{"packages":["ghc-8.10.3","cabal-install-3.6"],"sources":[{"key_url":"https://keyserver.ubuntu.com/pks/lookup?op=get&search=0x063dab2bdc0b3f9fcebc378bff3aeacef6f88286","sourceline":"deb http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main"}]}} + os: linux + - compiler: ghc-8.10.2 + addons: {"apt":{"packages":["ghc-8.10.2","cabal-install-3.6"],"sources":[{"key_url":"https://keyserver.ubuntu.com/pks/lookup?op=get&search=0x063dab2bdc0b3f9fcebc378bff3aeacef6f88286","sourceline":"deb http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main"}]}} + os: linux + - compiler: ghc-8.10.1 + addons: {"apt":{"packages":["ghc-8.10.1","cabal-install-3.6"],"sources":[{"key_url":"https://keyserver.ubuntu.com/pks/lookup?op=get&search=0x063dab2bdc0b3f9fcebc378bff3aeacef6f88286","sourceline":"deb http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main"}]}} + os: linux + - compiler: ghc-8.8.4 + addons: {"apt":{"packages":["ghc-8.8.4","cabal-install-3.6"],"sources":[{"key_url":"https://keyserver.ubuntu.com/pks/lookup?op=get&search=0x063dab2bdc0b3f9fcebc378bff3aeacef6f88286","sourceline":"deb http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main"}]}} + os: linux + - compiler: ghc-8.8.3 + addons: {"apt":{"packages":["ghc-8.8.3","cabal-install-3.6"],"sources":[{"key_url":"https://keyserver.ubuntu.com/pks/lookup?op=get&search=0x063dab2bdc0b3f9fcebc378bff3aeacef6f88286","sourceline":"deb http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main"}]}} + os: linux + - compiler: ghc-8.8.2 + addons: {"apt":{"packages":["ghc-8.8.2","cabal-install-3.6"],"sources":[{"key_url":"https://keyserver.ubuntu.com/pks/lookup?op=get&search=0x063dab2bdc0b3f9fcebc378bff3aeacef6f88286","sourceline":"deb http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main"}]}} + os: linux + - compiler: ghc-8.8.1 + addons: {"apt":{"packages":["ghc-8.8.1","cabal-install-3.6"],"sources":[{"key_url":"https://keyserver.ubuntu.com/pks/lookup?op=get&search=0x063dab2bdc0b3f9fcebc378bff3aeacef6f88286","sourceline":"deb http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main"}]}} + os: linux + - compiler: ghc-8.6.5 + addons: {"apt":{"packages":["ghc-8.6.5","cabal-install-3.6"],"sources":[{"key_url":"https://keyserver.ubuntu.com/pks/lookup?op=get&search=0x063dab2bdc0b3f9fcebc378bff3aeacef6f88286","sourceline":"deb http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main"}]}} + os: linux + - compiler: ghc-8.6.4 + addons: {"apt":{"packages":["ghc-8.6.4","cabal-install-3.6"],"sources":[{"key_url":"https://keyserver.ubuntu.com/pks/lookup?op=get&search=0x063dab2bdc0b3f9fcebc378bff3aeacef6f88286","sourceline":"deb http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main"}]}} + os: linux + - compiler: ghc-8.6.3 + addons: {"apt":{"packages":["ghc-8.6.3","cabal-install-3.6"],"sources":[{"key_url":"https://keyserver.ubuntu.com/pks/lookup?op=get&search=0x063dab2bdc0b3f9fcebc378bff3aeacef6f88286","sourceline":"deb http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main"}]}} + os: linux + - compiler: ghc-8.6.2 + addons: {"apt":{"packages":["ghc-8.6.2","cabal-install-3.6"],"sources":[{"key_url":"https://keyserver.ubuntu.com/pks/lookup?op=get&search=0x063dab2bdc0b3f9fcebc378bff3aeacef6f88286","sourceline":"deb http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main"}]}} + os: linux + - compiler: ghc-8.6.1 + addons: {"apt":{"packages":["ghc-8.6.1","cabal-install-3.6"],"sources":[{"key_url":"https://keyserver.ubuntu.com/pks/lookup?op=get&search=0x063dab2bdc0b3f9fcebc378bff3aeacef6f88286","sourceline":"deb http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main"}]}} + os: linux + - compiler: ghc-8.4.4 + addons: {"apt":{"packages":["ghc-8.4.4","cabal-install-3.6"],"sources":[{"key_url":"https://keyserver.ubuntu.com/pks/lookup?op=get&search=0x063dab2bdc0b3f9fcebc378bff3aeacef6f88286","sourceline":"deb http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main"}]}} + os: linux + - compiler: ghc-8.4.3 + addons: {"apt":{"packages":["ghc-8.4.3","cabal-install-3.6"],"sources":[{"key_url":"https://keyserver.ubuntu.com/pks/lookup?op=get&search=0x063dab2bdc0b3f9fcebc378bff3aeacef6f88286","sourceline":"deb http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main"}]}} + os: linux + - compiler: ghc-8.4.2 + addons: {"apt":{"packages":["ghc-8.4.2","cabal-install-3.6"],"sources":[{"key_url":"https://keyserver.ubuntu.com/pks/lookup?op=get&search=0x063dab2bdc0b3f9fcebc378bff3aeacef6f88286","sourceline":"deb http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main"}]}} + os: linux + - compiler: ghc-8.4.1 + addons: {"apt":{"packages":["ghc-8.4.1","cabal-install-3.6"],"sources":[{"key_url":"https://keyserver.ubuntu.com/pks/lookup?op=get&search=0x063dab2bdc0b3f9fcebc378bff3aeacef6f88286","sourceline":"deb http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main"}]}} + os: linux + - compiler: ghc-8.2.2 + addons: {"apt":{"packages":["ghc-8.2.2","cabal-install-3.6"],"sources":[{"key_url":"https://keyserver.ubuntu.com/pks/lookup?op=get&search=0x063dab2bdc0b3f9fcebc378bff3aeacef6f88286","sourceline":"deb http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main"}]}} + os: linux + - compiler: ghc-8.2.1 + addons: {"apt":{"packages":["ghc-8.2.1","cabal-install-3.6"],"sources":[{"key_url":"https://keyserver.ubuntu.com/pks/lookup?op=get&search=0x063dab2bdc0b3f9fcebc378bff3aeacef6f88286","sourceline":"deb http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main"}]}} + os: linux + - compiler: ghc-8.0.2 + addons: {"apt":{"packages":["ghc-8.0.2","cabal-install-3.6"],"sources":[{"key_url":"https://keyserver.ubuntu.com/pks/lookup?op=get&search=0x063dab2bdc0b3f9fcebc378bff3aeacef6f88286","sourceline":"deb http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main"}]}} + os: linux + - compiler: ghc-8.0.1 + addons: {"apt":{"packages":["ghc-8.0.1","cabal-install-3.6"],"sources":[{"key_url":"https://keyserver.ubuntu.com/pks/lookup?op=get&search=0x063dab2bdc0b3f9fcebc378bff3aeacef6f88286","sourceline":"deb http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main"}]}} + os: linux + - compiler: ghc-7.10.3 + addons: {"apt":{"packages":["ghc-7.10.3","cabal-install-3.6"],"sources":[{"key_url":"https://keyserver.ubuntu.com/pks/lookup?op=get&search=0x063dab2bdc0b3f9fcebc378bff3aeacef6f88286","sourceline":"deb http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main"}]}} + os: linux + - compiler: ghc-7.10.2 + addons: {"apt":{"packages":["ghc-7.10.2","cabal-install-3.6"],"sources":[{"key_url":"https://keyserver.ubuntu.com/pks/lookup?op=get&search=0x063dab2bdc0b3f9fcebc378bff3aeacef6f88286","sourceline":"deb http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main"}]}} + os: linux + - compiler: ghc-7.10.1 + addons: {"apt":{"packages":["ghc-7.10.1","cabal-install-3.6"],"sources":[{"key_url":"https://keyserver.ubuntu.com/pks/lookup?op=get&search=0x063dab2bdc0b3f9fcebc378bff3aeacef6f88286","sourceline":"deb http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main"}]}} + os: linux + - compiler: ghc-7.8.4 + addons: {"apt":{"packages":["ghc-7.8.4","cabal-install-3.6"],"sources":[{"key_url":"https://keyserver.ubuntu.com/pks/lookup?op=get&search=0x063dab2bdc0b3f9fcebc378bff3aeacef6f88286","sourceline":"deb http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main"}]}} + os: linux + - compiler: ghc-7.8.3 + addons: {"apt":{"packages":["ghc-7.8.3","cabal-install-3.6"],"sources":[{"key_url":"https://keyserver.ubuntu.com/pks/lookup?op=get&search=0x063dab2bdc0b3f9fcebc378bff3aeacef6f88286","sourceline":"deb http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main"}]}} + os: linux + - compiler: ghc-7.8.2 + addons: {"apt":{"packages":["ghc-7.8.2","cabal-install-3.6"],"sources":[{"key_url":"https://keyserver.ubuntu.com/pks/lookup?op=get&search=0x063dab2bdc0b3f9fcebc378bff3aeacef6f88286","sourceline":"deb http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main"}]}} + os: linux + - compiler: ghc-7.8.1 + addons: {"apt":{"packages":["ghc-7.8.1","cabal-install-3.6"],"sources":[{"key_url":"https://keyserver.ubuntu.com/pks/lookup?op=get&search=0x063dab2bdc0b3f9fcebc378bff3aeacef6f88286","sourceline":"deb http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main"}]}} + os: linux +before_install: + - HC=$(echo "/opt/$CC/bin/ghc" | sed 's/-/\//') + - WITHCOMPILER="-w $HC" + - HADDOCK=$(echo "/opt/$CC/bin/haddock" | sed 's/-/\//') + - HCPKG="$HC-pkg" + - unset CC + - CABAL=/opt/ghc/bin/cabal + - CABALHOME=$HOME/.cabal + - export PATH="$CABALHOME/bin:$PATH" + - TOP=$(pwd) + - "HCNUMVER=$(${HC} --numeric-version|perl -ne '/^(\\d+)\\.(\\d+)\\.(\\d+)(\\.(\\d+))?$/; print(10000 * $1 + 100 * $2 + ($3 == 0 ? $5 != 1 : $3))')" + - echo $HCNUMVER + - CABAL="$CABAL -vnormal+nowrap" + - set -o pipefail + - TEST=--enable-tests + - BENCH=--enable-benchmarks + - HEADHACKAGE=false + - rm -f $CABALHOME/config + - | + echo "verbose: normal +nowrap +markoutput" >> $CABALHOME/config + echo "remote-build-reporting: anonymous" >> $CABALHOME/config + echo "write-ghc-environment-files: never" >> $CABALHOME/config + echo "remote-repo-cache: $CABALHOME/packages" >> $CABALHOME/config + echo "logs-dir: $CABALHOME/logs" >> $CABALHOME/config + echo "world-file: $CABALHOME/world" >> $CABALHOME/config + echo "extra-prog-path: $CABALHOME/bin" >> $CABALHOME/config + echo "symlink-bindir: $CABALHOME/bin" >> $CABALHOME/config + echo "installdir: $CABALHOME/bin" >> $CABALHOME/config + echo "build-summary: $CABALHOME/logs/build.log" >> $CABALHOME/config + echo "store-dir: $CABALHOME/store" >> $CABALHOME/config + echo "install-dirs user" >> $CABALHOME/config + echo " prefix: $CABALHOME" >> $CABALHOME/config + echo "repository hackage.haskell.org" >> $CABALHOME/config + echo " url: http://hackage.haskell.org/" >> $CABALHOME/config +install: + - ${CABAL} --version + - echo "$(${HC} --version) [$(${HC} --print-project-git-commit-id 2> /dev/null || echo '?')]" + - | + echo "program-default-options" >> $CABALHOME/config + echo " ghc-options: $GHCJOBS +RTS -M6G -RTS" >> $CABALHOME/config + - cat $CABALHOME/config + - rm -fv cabal.project cabal.project.local cabal.project.freeze + - travis_retry ${CABAL} v2-update -v + # Generate cabal.project + - rm -rf cabal.project cabal.project.local cabal.project.freeze + - touch cabal.project + - | + echo "packages: servant" >> cabal.project + - if [ $((HCNUMVER >= 80200)) -ne 0 ] ; then echo 'package servant' >> cabal.project ; fi + - "if [ $((HCNUMVER >= 80200)) -ne 0 ] ; then echo ' ghc-options: -Werror=missing-methods' >> cabal.project ; fi" + - "" + - "for pkg in $($HCPKG list --simple-output); do echo $pkg | sed 's/-[^-]*$//' | (grep -vE -- '^(servant)$' || true) | sed 's/^/constraints: /' | sed 's/$/ installed/' >> cabal.project.local; done" + - cat cabal.project || true + - cat cabal.project.local || true + - if [ -f "servant/configure.ac" ]; then (cd "servant" && autoreconf -i); fi + - ${CABAL} v2-freeze $WITHCOMPILER ${TEST} ${BENCH} + - "cat cabal.project.freeze | sed -E 's/^(constraints: *| *)//' | sed 's/any.//'" + - rm cabal.project.freeze + - travis_wait 40 ${CABAL} v2-build $WITHCOMPILER ${TEST} ${BENCH} --dep -j2 all + - travis_wait 40 ${CABAL} v2-build $WITHCOMPILER --disable-tests --disable-benchmarks --dep -j2 all +script: + - DISTDIR=$(mktemp -d /tmp/dist-test.XXXX) + # Packaging... + - ${CABAL} v2-sdist all + # Unpacking... + - mv dist-newstyle/sdist/*.tar.gz ${DISTDIR}/ + - cd ${DISTDIR} || false + - find . -maxdepth 1 -type f -name '*.tar.gz' -exec tar -xvf '{}' \; + - find . -maxdepth 1 -type f -name '*.tar.gz' -exec rm '{}' \; + - PKGDIR_servant="$(find . -maxdepth 1 -type d -regex '.*/servant-[0-9.]*')" + # Generate cabal.project + - rm -rf cabal.project cabal.project.local cabal.project.freeze + - touch cabal.project + - | + echo "packages: ${PKGDIR_servant}" >> cabal.project + - if [ $((HCNUMVER >= 80200)) -ne 0 ] ; then echo 'package servant' >> cabal.project ; fi + - "if [ $((HCNUMVER >= 80200)) -ne 0 ] ; then echo ' ghc-options: -Werror=missing-methods' >> cabal.project ; fi" + - "" + - "for pkg in $($HCPKG list --simple-output); do echo $pkg | sed 's/-[^-]*$//' | (grep -vE -- '^(servant)$' || true) | sed 's/^/constraints: /' | sed 's/$/ installed/' >> cabal.project.local; done" + - cat cabal.project || true + - cat cabal.project.local || true + # Building... + # this builds all libraries and executables (without tests/benchmarks) + - ${CABAL} v2-build $WITHCOMPILER --disable-tests --disable-benchmarks all + # Building with tests and benchmarks... + # build & run tests, build benchmarks + - ${CABAL} v2-build $WITHCOMPILER ${TEST} ${BENCH} all --write-ghc-environment-files=always + # Testing... + - ${CABAL} v2-test $WITHCOMPILER ${TEST} ${BENCH} all --test-show-details=direct + # cabal check... + - (cd ${PKGDIR_servant} && ${CABAL} -vnormal check) + # haddock... + - ${CABAL} v2-haddock $WITHCOMPILER --with-haddock $HADDOCK ${TEST} ${BENCH} all + # Building without installed constraints for packages in global-db... + - rm -f cabal.project.local + - ${CABAL} v2-build $WITHCOMPILER --disable-tests --disable-benchmarks all + +# REGENDATA ["--sourcehut-parallel","travis","sourcehut-parallel.project","--sourcehut-source","https://example.org"] +# EOF diff --git a/test/Tests.hs b/test/Tests.hs index c6d7859f..d3055df5 100644 --- a/test/Tests.hs +++ b/test/Tests.hs @@ -32,6 +32,7 @@ main = do , fixtureGoldenTest "psql" , fixtureGoldenTest "travis-patch" , fixtureGoldenTest "enabled-jobs" + , fixtureGoldenTest "sourcehut-parallel" , testGroup "copy-fields" [ fixtureGoldenTest "copy-fields-all" , fixtureGoldenTest "copy-fields-some" From cb072bb3673b6d48953c0152b70e7c7c0d52cee4 Mon Sep 17 00:00:00 2001 From: Francesco Gazzetta Date: Mon, 29 Nov 2021 20:58:54 +0100 Subject: [PATCH 17/23] Remove unused extension --- src/HaskellCI.hs | 1 - 1 file changed, 1 deletion(-) diff --git a/src/HaskellCI.hs b/src/HaskellCI.hs index e233bde6..976589bb 100644 --- a/src/HaskellCI.hs +++ b/src/HaskellCI.hs @@ -1,6 +1,5 @@ {-# LANGUAGE DataKinds #-} {-# LANGUAGE MultiWayIf #-} -{-# LANGUAGE NamedFieldPuns #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeApplications #-} From 8f9dbe272438ff376acebcd50d6763897e05c6a6 Mon Sep 17 00:00:00 2001 From: Francesco Gazzetta Date: Wed, 1 Dec 2021 15:39:09 +0100 Subject: [PATCH 18/23] Use Cabal's ordNub instead of containers' nubOrd The one from containers was only added relatively recently and it's not included in GHC 8.2 --- src/HaskellCI/Sourcehut.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/src/HaskellCI/Sourcehut.hs b/src/HaskellCI/Sourcehut.hs index 424cf9c1..2f7f7f18 100644 --- a/src/HaskellCI/Sourcehut.hs +++ b/src/HaskellCI/Sourcehut.hs @@ -9,7 +9,6 @@ module HaskellCI.Sourcehut ( import HaskellCI.Prelude -import Data.Containers.ListUtils (nubOrd) import qualified Data.Map.Strict as M import qualified Data.Set as S import qualified Data.Text as T @@ -18,6 +17,7 @@ import qualified Distribution.Types.GenericPackageDescription as C import qualified Distribution.Types.PackageDescription as C import qualified Distribution.Types.VersionRange as C import qualified Distribution.Utils.ShortText as C +import qualified Distribution.Simple.Utils as C import System.FilePath.Posix (takeFileName) import Cabal.Project @@ -134,7 +134,7 @@ makeSourcehut' config@Config {..} source prj jobs@JobVersions {..} = , srhtManifestArtifacts = [] , srhtManifestSources = [source] , srhtManifestTasks = prepare : tasks - , srhtManifestTriggers = SourcehutTriggerEmail <$> nubOrd (getEmails prj) + , srhtManifestTriggers = SourcehutTriggerEmail <$> C.ordNub (getEmails prj) , srhtManifestEnvironment = mempty } From 3c2894f3f30c6f3c964829a10f4e4c058027ee39 Mon Sep 17 00:00:00 2001 From: Francesco Gazzetta Date: Sun, 19 Dec 2021 19:27:26 +0100 Subject: [PATCH 19/23] Use --sourcehut-source only in sourcehut tests --- fixtures/all-versions.bash | 2 +- fixtures/all-versions.github | 4 ++-- fixtures/all-versions.travis | 4 ++-- fixtures/copy-fields-all.bash | 2 +- fixtures/copy-fields-all.github | 4 ++-- fixtures/copy-fields-all.travis | 4 ++-- fixtures/copy-fields-none.bash | 2 +- fixtures/copy-fields-none.github | 4 ++-- fixtures/copy-fields-none.travis | 4 ++-- fixtures/copy-fields-some.bash | 2 +- fixtures/copy-fields-some.github | 4 ++-- fixtures/copy-fields-some.travis | 4 ++-- fixtures/empty-line.bash | 2 +- fixtures/empty-line.github | 4 ++-- fixtures/empty-line.travis | 4 ++-- fixtures/enabled-jobs.bash | 2 +- fixtures/enabled-jobs.github | 4 ++-- fixtures/enabled-jobs.travis | 4 ++-- fixtures/irc-channels.bash | 2 +- fixtures/irc-channels.github | 4 ++-- fixtures/irc-channels.travis | 4 ++-- fixtures/messy.bash | 2 +- fixtures/messy.github | 4 ++-- fixtures/messy.travis | 4 ++-- fixtures/psql.bash | 2 +- fixtures/psql.github | 4 ++-- fixtures/psql.travis | 4 ++-- fixtures/sourcehut-parallel.bash | 2 +- fixtures/sourcehut-parallel.github | 4 ++-- fixtures/sourcehut-parallel.travis | 4 ++-- fixtures/travis-patch.bash | 2 +- fixtures/travis-patch.github | 4 ++-- fixtures/travis-patch.travis | 4 ++-- test/Tests.hs | 4 +++- 34 files changed, 58 insertions(+), 56 deletions(-) diff --git a/fixtures/all-versions.bash b/fixtures/all-versions.bash index 6e12dfcb..60a75527 100644 --- a/fixtures/all-versions.bash +++ b/fixtures/all-versions.bash @@ -2,7 +2,7 @@ # *INFO* Generating Bash script for testing for GHC versions: 7.0.1 7.0.2 7.0.3 7.0.4 7.2.1 7.2.2 7.4.1 7.4.2 7.6.1 7.6.2 7.6.3 7.8.1 7.8.2 7.8.3 7.8.4 7.10.1 7.10.2 7.10.3 8.0.1 8.0.2 8.2.1 8.2.2 8.4.1 8.4.2 8.4.3 8.4.4 8.6.1 8.6.2 8.6.3 8.6.4 8.6.5 8.8.1 8.8.2 8.8.3 8.8.4 8.10.1 8.10.2 8.10.3 8.10.4 8.10.5 8.10.6 8.10.7 9.0.1 9.0.2 9.2.1 9.2.2 9.2.3 9.4.1 ghcjs-8.4 #!/bin/bash # shellcheck disable=SC2086,SC2016,SC2046 -# REGENDATA ["bash","all-versions.project","--sourcehut-source","https://example.org"] +# REGENDATA ["bash","all-versions.project"] set -o pipefail diff --git a/fixtures/all-versions.github b/fixtures/all-versions.github index e50dbe82..a8f4955f 100644 --- a/fixtures/all-versions.github +++ b/fixtures/all-versions.github @@ -2,7 +2,7 @@ # *INFO* Generating GitHub config for testing for GHC versions: 7.0.1 7.0.2 7.0.3 7.0.4 7.2.1 7.2.2 7.4.1 7.4.2 7.6.1 7.6.2 7.6.3 7.8.1 7.8.2 7.8.3 7.8.4 7.10.1 7.10.2 7.10.3 8.0.1 8.0.2 8.2.1 8.2.2 8.4.1 8.4.2 8.4.3 8.4.4 8.6.1 8.6.2 8.6.3 8.6.4 8.6.5 8.8.1 8.8.2 8.8.3 8.8.4 8.10.1 8.10.2 8.10.3 8.10.4 8.10.5 8.10.6 8.10.7 9.0.1 9.0.2 9.2.1 9.2.2 9.2.3 9.4.1 ghcjs-8.4 # This GitHub workflow config has been generated by a script via # -# haskell-ci 'github' 'all-versions.project' '--sourcehut-source' 'https://example.org' +# haskell-ci 'github' 'all-versions.project' # # To regenerate the script (for example after adjusting tested-with) run # @@ -10,7 +10,7 @@ # # For more information, see https://github.com/haskell-CI/haskell-ci # -# REGENDATA ["github","all-versions.project","--sourcehut-source","https://example.org"] +# REGENDATA ["github","all-versions.project"] # name: Haskell-CI on: diff --git a/fixtures/all-versions.travis b/fixtures/all-versions.travis index 29495a80..144ee587 100644 --- a/fixtures/all-versions.travis +++ b/fixtures/all-versions.travis @@ -2,7 +2,7 @@ # *INFO* Generating Travis-CI config for testing for GHC versions: 7.0.1 7.0.2 7.0.3 7.0.4 7.2.1 7.2.2 7.4.1 7.4.2 7.6.1 7.6.2 7.6.3 7.8.1 7.8.2 7.8.3 7.8.4 7.10.1 7.10.2 7.10.3 8.0.1 8.0.2 8.2.1 8.2.2 8.4.1 8.4.2 8.4.3 8.4.4 8.6.1 8.6.2 8.6.3 8.6.4 8.6.5 8.8.1 8.8.2 8.8.3 8.8.4 8.10.1 8.10.2 8.10.3 8.10.4 8.10.5 8.10.6 8.10.7 9.0.1 9.0.2 9.2.1 9.2.2 9.2.3 9.4.1 ghcjs-8.4 # This Travis job script has been generated by a script via # -# haskell-ci 'travis' 'all-versions.project' '--sourcehut-source' 'https://example.org' +# haskell-ci 'travis' 'all-versions.project' # # To regenerate the script (for example after adjusting tested-with) run # @@ -310,5 +310,5 @@ script: - rm -f cabal.project.local - ${CABAL} v2-build $WITHCOMPILER --disable-tests --disable-benchmarks all -# REGENDATA ["travis","all-versions.project","--sourcehut-source","https://example.org"] +# REGENDATA ["travis","all-versions.project"] # EOF diff --git a/fixtures/copy-fields-all.bash b/fixtures/copy-fields-all.bash index 954a16b2..d5dbc605 100644 --- a/fixtures/copy-fields-all.bash +++ b/fixtures/copy-fields-all.bash @@ -2,7 +2,7 @@ # *INFO* Generating Bash script for testing for GHC versions: 7.8.1 7.8.2 7.8.3 7.8.4 7.10.1 7.10.2 7.10.3 8.0.1 8.0.2 8.2.1 8.2.2 8.4.1 8.4.2 8.4.3 8.4.4 8.6.1 8.6.2 8.6.3 8.6.4 8.6.5 8.8.1 8.8.2 8.8.3 8.8.4 8.10.1 8.10.2 8.10.3 8.10.4 8.10.5 8.10.6 8.10.7 #!/bin/bash # shellcheck disable=SC2086,SC2016,SC2046 -# REGENDATA ["--copy-fields=all","bash","copy-fields-all.project","--sourcehut-source","https://example.org"] +# REGENDATA ["--copy-fields=all","bash","copy-fields-all.project"] set -o pipefail diff --git a/fixtures/copy-fields-all.github b/fixtures/copy-fields-all.github index fe9706e6..0aa7fc5d 100644 --- a/fixtures/copy-fields-all.github +++ b/fixtures/copy-fields-all.github @@ -2,7 +2,7 @@ # *INFO* Generating GitHub config for testing for GHC versions: 7.8.1 7.8.2 7.8.3 7.8.4 7.10.1 7.10.2 7.10.3 8.0.1 8.0.2 8.2.1 8.2.2 8.4.1 8.4.2 8.4.3 8.4.4 8.6.1 8.6.2 8.6.3 8.6.4 8.6.5 8.8.1 8.8.2 8.8.3 8.8.4 8.10.1 8.10.2 8.10.3 8.10.4 8.10.5 8.10.6 8.10.7 # This GitHub workflow config has been generated by a script via # -# haskell-ci '--copy-fields=all' 'github' 'copy-fields-all.project' '--sourcehut-source' 'https://example.org' +# haskell-ci '--copy-fields=all' 'github' 'copy-fields-all.project' # # To regenerate the script (for example after adjusting tested-with) run # @@ -10,7 +10,7 @@ # # For more information, see https://github.com/haskell-CI/haskell-ci # -# REGENDATA ["--copy-fields=all","github","copy-fields-all.project","--sourcehut-source","https://example.org"] +# REGENDATA ["--copy-fields=all","github","copy-fields-all.project"] # name: Haskell-CI on: diff --git a/fixtures/copy-fields-all.travis b/fixtures/copy-fields-all.travis index 715a38bb..be09d4e1 100644 --- a/fixtures/copy-fields-all.travis +++ b/fixtures/copy-fields-all.travis @@ -2,7 +2,7 @@ # *INFO* Generating Travis-CI config for testing for GHC versions: 7.8.1 7.8.2 7.8.3 7.8.4 7.10.1 7.10.2 7.10.3 8.0.1 8.0.2 8.2.1 8.2.2 8.4.1 8.4.2 8.4.3 8.4.4 8.6.1 8.6.2 8.6.3 8.6.4 8.6.5 8.8.1 8.8.2 8.8.3 8.8.4 8.10.1 8.10.2 8.10.3 8.10.4 8.10.5 8.10.6 8.10.7 # This Travis job script has been generated by a script via # -# haskell-ci '--copy-fields=all' 'travis' 'copy-fields-all.project' '--sourcehut-source' 'https://example.org' +# haskell-ci '--copy-fields=all' 'travis' 'copy-fields-all.project' # # To regenerate the script (for example after adjusting tested-with) run # @@ -272,5 +272,5 @@ script: - rm -f cabal.project.local - ${CABAL} v2-build $WITHCOMPILER --disable-tests --disable-benchmarks all -# REGENDATA ["--copy-fields=all","travis","copy-fields-all.project","--sourcehut-source","https://example.org"] +# REGENDATA ["--copy-fields=all","travis","copy-fields-all.project"] # EOF diff --git a/fixtures/copy-fields-none.bash b/fixtures/copy-fields-none.bash index bdebf4db..edf57075 100644 --- a/fixtures/copy-fields-none.bash +++ b/fixtures/copy-fields-none.bash @@ -2,7 +2,7 @@ # *INFO* Generating Bash script for testing for GHC versions: 7.8.1 7.8.2 7.8.3 7.8.4 7.10.1 7.10.2 7.10.3 8.0.1 8.0.2 8.2.1 8.2.2 8.4.1 8.4.2 8.4.3 8.4.4 8.6.1 8.6.2 8.6.3 8.6.4 8.6.5 8.8.1 8.8.2 8.8.3 8.8.4 8.10.1 8.10.2 8.10.3 8.10.4 8.10.5 8.10.6 8.10.7 #!/bin/bash # shellcheck disable=SC2086,SC2016,SC2046 -# REGENDATA ["--copy-fields=none","bash","copy-fields-none.project","--sourcehut-source","https://example.org"] +# REGENDATA ["--copy-fields=none","bash","copy-fields-none.project"] set -o pipefail diff --git a/fixtures/copy-fields-none.github b/fixtures/copy-fields-none.github index a853a291..6119f240 100644 --- a/fixtures/copy-fields-none.github +++ b/fixtures/copy-fields-none.github @@ -2,7 +2,7 @@ # *INFO* Generating GitHub config for testing for GHC versions: 7.8.1 7.8.2 7.8.3 7.8.4 7.10.1 7.10.2 7.10.3 8.0.1 8.0.2 8.2.1 8.2.2 8.4.1 8.4.2 8.4.3 8.4.4 8.6.1 8.6.2 8.6.3 8.6.4 8.6.5 8.8.1 8.8.2 8.8.3 8.8.4 8.10.1 8.10.2 8.10.3 8.10.4 8.10.5 8.10.6 8.10.7 # This GitHub workflow config has been generated by a script via # -# haskell-ci '--copy-fields=none' 'github' 'copy-fields-none.project' '--sourcehut-source' 'https://example.org' +# haskell-ci '--copy-fields=none' 'github' 'copy-fields-none.project' # # To regenerate the script (for example after adjusting tested-with) run # @@ -10,7 +10,7 @@ # # For more information, see https://github.com/haskell-CI/haskell-ci # -# REGENDATA ["--copy-fields=none","github","copy-fields-none.project","--sourcehut-source","https://example.org"] +# REGENDATA ["--copy-fields=none","github","copy-fields-none.project"] # name: Haskell-CI on: diff --git a/fixtures/copy-fields-none.travis b/fixtures/copy-fields-none.travis index de8edfb2..b653543a 100644 --- a/fixtures/copy-fields-none.travis +++ b/fixtures/copy-fields-none.travis @@ -2,7 +2,7 @@ # *INFO* Generating Travis-CI config for testing for GHC versions: 7.8.1 7.8.2 7.8.3 7.8.4 7.10.1 7.10.2 7.10.3 8.0.1 8.0.2 8.2.1 8.2.2 8.4.1 8.4.2 8.4.3 8.4.4 8.6.1 8.6.2 8.6.3 8.6.4 8.6.5 8.8.1 8.8.2 8.8.3 8.8.4 8.10.1 8.10.2 8.10.3 8.10.4 8.10.5 8.10.6 8.10.7 # This Travis job script has been generated by a script via # -# haskell-ci '--copy-fields=none' 'travis' 'copy-fields-none.project' '--sourcehut-source' 'https://example.org' +# haskell-ci '--copy-fields=none' 'travis' 'copy-fields-none.project' # # To regenerate the script (for example after adjusting tested-with) run # @@ -250,5 +250,5 @@ script: - rm -f cabal.project.local - ${CABAL} v2-build $WITHCOMPILER --disable-tests --disable-benchmarks all -# REGENDATA ["--copy-fields=none","travis","copy-fields-none.project","--sourcehut-source","https://example.org"] +# REGENDATA ["--copy-fields=none","travis","copy-fields-none.project"] # EOF diff --git a/fixtures/copy-fields-some.bash b/fixtures/copy-fields-some.bash index 05aecaac..78b1ec69 100644 --- a/fixtures/copy-fields-some.bash +++ b/fixtures/copy-fields-some.bash @@ -2,7 +2,7 @@ # *INFO* Generating Bash script for testing for GHC versions: 7.8.1 7.8.2 7.8.3 7.8.4 7.10.1 7.10.2 7.10.3 8.0.1 8.0.2 8.2.1 8.2.2 8.4.1 8.4.2 8.4.3 8.4.4 8.6.1 8.6.2 8.6.3 8.6.4 8.6.5 8.8.1 8.8.2 8.8.3 8.8.4 8.10.1 8.10.2 8.10.3 8.10.4 8.10.5 8.10.6 8.10.7 #!/bin/bash # shellcheck disable=SC2086,SC2016,SC2046 -# REGENDATA ["--copy-fields=some","bash","copy-fields-some.project","--sourcehut-source","https://example.org"] +# REGENDATA ["--copy-fields=some","bash","copy-fields-some.project"] set -o pipefail diff --git a/fixtures/copy-fields-some.github b/fixtures/copy-fields-some.github index 295b9eb8..5948954a 100644 --- a/fixtures/copy-fields-some.github +++ b/fixtures/copy-fields-some.github @@ -2,7 +2,7 @@ # *INFO* Generating GitHub config for testing for GHC versions: 7.8.1 7.8.2 7.8.3 7.8.4 7.10.1 7.10.2 7.10.3 8.0.1 8.0.2 8.2.1 8.2.2 8.4.1 8.4.2 8.4.3 8.4.4 8.6.1 8.6.2 8.6.3 8.6.4 8.6.5 8.8.1 8.8.2 8.8.3 8.8.4 8.10.1 8.10.2 8.10.3 8.10.4 8.10.5 8.10.6 8.10.7 # This GitHub workflow config has been generated by a script via # -# haskell-ci '--copy-fields=some' 'github' 'copy-fields-some.project' '--sourcehut-source' 'https://example.org' +# haskell-ci '--copy-fields=some' 'github' 'copy-fields-some.project' # # To regenerate the script (for example after adjusting tested-with) run # @@ -10,7 +10,7 @@ # # For more information, see https://github.com/haskell-CI/haskell-ci # -# REGENDATA ["--copy-fields=some","github","copy-fields-some.project","--sourcehut-source","https://example.org"] +# REGENDATA ["--copy-fields=some","github","copy-fields-some.project"] # name: Haskell-CI on: diff --git a/fixtures/copy-fields-some.travis b/fixtures/copy-fields-some.travis index 73aa458f..5fbc55e2 100644 --- a/fixtures/copy-fields-some.travis +++ b/fixtures/copy-fields-some.travis @@ -2,7 +2,7 @@ # *INFO* Generating Travis-CI config for testing for GHC versions: 7.8.1 7.8.2 7.8.3 7.8.4 7.10.1 7.10.2 7.10.3 8.0.1 8.0.2 8.2.1 8.2.2 8.4.1 8.4.2 8.4.3 8.4.4 8.6.1 8.6.2 8.6.3 8.6.4 8.6.5 8.8.1 8.8.2 8.8.3 8.8.4 8.10.1 8.10.2 8.10.3 8.10.4 8.10.5 8.10.6 8.10.7 # This Travis job script has been generated by a script via # -# haskell-ci '--copy-fields=some' 'travis' 'copy-fields-some.project' '--sourcehut-source' 'https://example.org' +# haskell-ci '--copy-fields=some' 'travis' 'copy-fields-some.project' # # To regenerate the script (for example after adjusting tested-with) run # @@ -256,5 +256,5 @@ script: - rm -f cabal.project.local - ${CABAL} v2-build $WITHCOMPILER --disable-tests --disable-benchmarks all -# REGENDATA ["--copy-fields=some","travis","copy-fields-some.project","--sourcehut-source","https://example.org"] +# REGENDATA ["--copy-fields=some","travis","copy-fields-some.project"] # EOF diff --git a/fixtures/empty-line.bash b/fixtures/empty-line.bash index 9a435f9f..f0337f9b 100644 --- a/fixtures/empty-line.bash +++ b/fixtures/empty-line.bash @@ -2,7 +2,7 @@ # *INFO* Generating Bash script for testing for GHC versions: ghc-head 7.8.1 7.8.2 7.8.3 7.8.4 7.10.1 7.10.2 7.10.3 8.0.1 8.0.2 8.2.1 8.2.2 8.4.1 8.4.2 8.4.3 8.4.4 8.6.1 8.6.2 8.6.3 8.6.4 8.6.5 8.8.1 8.8.2 8.8.3 8.8.4 8.10.1 8.10.2 8.10.3 8.10.4 8.10.5 8.10.6 8.10.7 #!/bin/bash # shellcheck disable=SC2086,SC2016,SC2046 -# REGENDATA ["--ghc-head","bash","empty-line.project","--sourcehut-source","https://example.org"] +# REGENDATA ["--ghc-head","bash","empty-line.project"] set -o pipefail diff --git a/fixtures/empty-line.github b/fixtures/empty-line.github index 0c09e255..ca3b9368 100644 --- a/fixtures/empty-line.github +++ b/fixtures/empty-line.github @@ -2,7 +2,7 @@ # *INFO* Generating GitHub config for testing for GHC versions: ghc-head 7.8.1 7.8.2 7.8.3 7.8.4 7.10.1 7.10.2 7.10.3 8.0.1 8.0.2 8.2.1 8.2.2 8.4.1 8.4.2 8.4.3 8.4.4 8.6.1 8.6.2 8.6.3 8.6.4 8.6.5 8.8.1 8.8.2 8.8.3 8.8.4 8.10.1 8.10.2 8.10.3 8.10.4 8.10.5 8.10.6 8.10.7 # This GitHub workflow config has been generated by a script via # -# haskell-ci '--ghc-head' 'github' 'empty-line.project' '--sourcehut-source' 'https://example.org' +# haskell-ci '--ghc-head' 'github' 'empty-line.project' # # To regenerate the script (for example after adjusting tested-with) run # @@ -10,7 +10,7 @@ # # For more information, see https://github.com/haskell-CI/haskell-ci # -# REGENDATA ["--ghc-head","github","empty-line.project","--sourcehut-source","https://example.org"] +# REGENDATA ["--ghc-head","github","empty-line.project"] # name: Haskell-CI on: diff --git a/fixtures/empty-line.travis b/fixtures/empty-line.travis index 2bafaafb..18a692d8 100644 --- a/fixtures/empty-line.travis +++ b/fixtures/empty-line.travis @@ -2,7 +2,7 @@ # *INFO* Generating Travis-CI config for testing for GHC versions: ghc-head 7.8.1 7.8.2 7.8.3 7.8.4 7.10.1 7.10.2 7.10.3 8.0.1 8.0.2 8.2.1 8.2.2 8.4.1 8.4.2 8.4.3 8.4.4 8.6.1 8.6.2 8.6.3 8.6.4 8.6.5 8.8.1 8.8.2 8.8.3 8.8.4 8.10.1 8.10.2 8.10.3 8.10.4 8.10.5 8.10.6 8.10.7 # This Travis job script has been generated by a script via # -# haskell-ci '--ghc-head' 'travis' 'empty-line.project' '--sourcehut-source' 'https://example.org' +# haskell-ci '--ghc-head' 'travis' 'empty-line.project' # # To regenerate the script (for example after adjusting tested-with) run # @@ -281,5 +281,5 @@ script: - rm -f cabal.project.local - ${CABAL} v2-build $WITHCOMPILER --disable-tests --disable-benchmarks all -# REGENDATA ["--ghc-head","travis","empty-line.project","--sourcehut-source","https://example.org"] +# REGENDATA ["--ghc-head","travis","empty-line.project"] # EOF diff --git a/fixtures/enabled-jobs.bash b/fixtures/enabled-jobs.bash index ba36b602..659b9e3a 100644 --- a/fixtures/enabled-jobs.bash +++ b/fixtures/enabled-jobs.bash @@ -2,7 +2,7 @@ # *INFO* Generating Bash script for testing for GHC versions: 8.0.1 8.0.2 8.2.1 8.2.2 8.4.1 8.4.2 8.4.3 8.4.4 8.6.1 8.6.2 8.6.3 8.6.4 8.6.5 8.8.1 8.8.2 8.8.3 8.8.4 8.10.1 8.10.2 8.10.3 8.10.4 8.10.5 8.10.6 8.10.7 9.0.1 9.0.2 9.2.1 9.2.2 9.2.3 9.4.1 ghcjs-8.4 #!/bin/bash # shellcheck disable=SC2086,SC2016,SC2046 -# REGENDATA ["--enabled-jobs=>=8","bash","enabled-jobs.project","--sourcehut-source","https://example.org"] +# REGENDATA ["--enabled-jobs=>=8","bash","enabled-jobs.project"] set -o pipefail diff --git a/fixtures/enabled-jobs.github b/fixtures/enabled-jobs.github index 2d5b6f75..a5eded8c 100644 --- a/fixtures/enabled-jobs.github +++ b/fixtures/enabled-jobs.github @@ -2,7 +2,7 @@ # *INFO* Generating GitHub config for testing for GHC versions: 8.0.1 8.0.2 8.2.1 8.2.2 8.4.1 8.4.2 8.4.3 8.4.4 8.6.1 8.6.2 8.6.3 8.6.4 8.6.5 8.8.1 8.8.2 8.8.3 8.8.4 8.10.1 8.10.2 8.10.3 8.10.4 8.10.5 8.10.6 8.10.7 9.0.1 9.0.2 9.2.1 9.2.2 9.2.3 9.4.1 ghcjs-8.4 # This GitHub workflow config has been generated by a script via # -# haskell-ci '--enabled-jobs=>=8' 'github' 'enabled-jobs.project' '--sourcehut-source' 'https://example.org' +# haskell-ci '--enabled-jobs=>=8' 'github' 'enabled-jobs.project' # # To regenerate the script (for example after adjusting tested-with) run # @@ -10,7 +10,7 @@ # # For more information, see https://github.com/haskell-CI/haskell-ci # -# REGENDATA ["--enabled-jobs=>=8","github","enabled-jobs.project","--sourcehut-source","https://example.org"] +# REGENDATA ["--enabled-jobs=>=8","github","enabled-jobs.project"] # name: Haskell-CI on: diff --git a/fixtures/enabled-jobs.travis b/fixtures/enabled-jobs.travis index 354a078c..3869bb49 100644 --- a/fixtures/enabled-jobs.travis +++ b/fixtures/enabled-jobs.travis @@ -2,7 +2,7 @@ # *INFO* Generating Travis-CI config for testing for GHC versions: 8.0.1 8.0.2 8.2.1 8.2.2 8.4.1 8.4.2 8.4.3 8.4.4 8.6.1 8.6.2 8.6.3 8.6.4 8.6.5 8.8.1 8.8.2 8.8.3 8.8.4 8.10.1 8.10.2 8.10.3 8.10.4 8.10.5 8.10.6 8.10.7 9.0.1 9.0.2 9.2.1 9.2.2 9.2.3 9.4.1 ghcjs-8.4 # This Travis job script has been generated by a script via # -# haskell-ci '--enabled-jobs=>=8' 'travis' 'enabled-jobs.project' '--sourcehut-source' 'https://example.org' +# haskell-ci '--enabled-jobs=>=8' 'travis' 'enabled-jobs.project' # # To regenerate the script (for example after adjusting tested-with) run # @@ -256,5 +256,5 @@ script: - rm -f cabal.project.local - ${CABAL} v2-build $WITHCOMPILER --disable-tests --disable-benchmarks all -# REGENDATA ["--enabled-jobs=>=8","travis","enabled-jobs.project","--sourcehut-source","https://example.org"] +# REGENDATA ["--enabled-jobs=>=8","travis","enabled-jobs.project"] # EOF diff --git a/fixtures/irc-channels.bash b/fixtures/irc-channels.bash index 519fd0a7..daf1ef4c 100644 --- a/fixtures/irc-channels.bash +++ b/fixtures/irc-channels.bash @@ -2,7 +2,7 @@ # *INFO* Generating Bash script for testing for GHC versions: 7.8.1 7.8.2 7.8.3 7.8.4 7.10.1 7.10.2 7.10.3 8.0.1 8.0.2 8.2.1 8.2.2 8.4.1 8.4.2 8.4.3 8.4.4 8.6.1 8.6.2 8.6.3 8.6.4 8.6.5 8.8.1 8.8.2 8.8.3 8.8.4 8.10.1 8.10.2 8.10.3 8.10.4 8.10.5 8.10.6 8.10.7 #!/bin/bash # shellcheck disable=SC2086,SC2016,SC2046 -# REGENDATA ["--irc-channels=irc.libera.chat#mychannel","bash","irc-channels.project","--sourcehut-source","https://example.org"] +# REGENDATA ["--irc-channels=irc.libera.chat#mychannel","bash","irc-channels.project"] set -o pipefail diff --git a/fixtures/irc-channels.github b/fixtures/irc-channels.github index 18135ca0..44547904 100644 --- a/fixtures/irc-channels.github +++ b/fixtures/irc-channels.github @@ -2,7 +2,7 @@ # *INFO* Generating GitHub config for testing for GHC versions: 7.8.1 7.8.2 7.8.3 7.8.4 7.10.1 7.10.2 7.10.3 8.0.1 8.0.2 8.2.1 8.2.2 8.4.1 8.4.2 8.4.3 8.4.4 8.6.1 8.6.2 8.6.3 8.6.4 8.6.5 8.8.1 8.8.2 8.8.3 8.8.4 8.10.1 8.10.2 8.10.3 8.10.4 8.10.5 8.10.6 8.10.7 # This GitHub workflow config has been generated by a script via # -# haskell-ci '--irc-channels=irc.libera.chat#mychannel' 'github' 'irc-channels.project' '--sourcehut-source' 'https://example.org' +# haskell-ci '--irc-channels=irc.libera.chat#mychannel' 'github' 'irc-channels.project' # # To regenerate the script (for example after adjusting tested-with) run # @@ -10,7 +10,7 @@ # # For more information, see https://github.com/haskell-CI/haskell-ci # -# REGENDATA ["--irc-channels=irc.libera.chat#mychannel","github","irc-channels.project","--sourcehut-source","https://example.org"] +# REGENDATA ["--irc-channels=irc.libera.chat#mychannel","github","irc-channels.project"] # name: Haskell-CI on: diff --git a/fixtures/irc-channels.travis b/fixtures/irc-channels.travis index d5c5ee0a..ca9a52ff 100644 --- a/fixtures/irc-channels.travis +++ b/fixtures/irc-channels.travis @@ -2,7 +2,7 @@ # *INFO* Generating Travis-CI config for testing for GHC versions: 7.8.1 7.8.2 7.8.3 7.8.4 7.10.1 7.10.2 7.10.3 8.0.1 8.0.2 8.2.1 8.2.2 8.4.1 8.4.2 8.4.3 8.4.4 8.6.1 8.6.2 8.6.3 8.6.4 8.6.5 8.8.1 8.8.2 8.8.3 8.8.4 8.10.1 8.10.2 8.10.3 8.10.4 8.10.5 8.10.6 8.10.7 # This Travis job script has been generated by a script via # -# haskell-ci '--irc-channels=irc.libera.chat#mychannel' 'travis' 'irc-channels.project' '--sourcehut-source' 'https://example.org' +# haskell-ci '--irc-channels=irc.libera.chat#mychannel' 'travis' 'irc-channels.project' # # To regenerate the script (for example after adjusting tested-with) run # @@ -230,5 +230,5 @@ script: - rm -f cabal.project.local - ${CABAL} v2-build $WITHCOMPILER --disable-tests --disable-benchmarks all -# REGENDATA ["--irc-channels=irc.libera.chat#mychannel","travis","irc-channels.project","--sourcehut-source","https://example.org"] +# REGENDATA ["--irc-channels=irc.libera.chat#mychannel","travis","irc-channels.project"] # EOF diff --git a/fixtures/messy.bash b/fixtures/messy.bash index 39032459..f27e082c 100644 --- a/fixtures/messy.bash +++ b/fixtures/messy.bash @@ -2,7 +2,7 @@ # *INFO* Generating Bash script for testing for GHC versions: ghc-head 7.8.1 7.8.2 7.8.3 7.8.4 7.10.1 7.10.2 7.10.3 8.0.1 8.0.2 8.2.1 8.2.2 8.4.1 8.4.2 8.4.3 8.4.4 8.6.1 8.6.2 8.6.3 8.6.4 8.6.5 8.8.1 8.8.2 8.8.3 8.8.4 8.10.1 8.10.2 8.10.3 8.10.4 8.10.5 8.10.6 8.10.7 #!/bin/bash # shellcheck disable=SC2086,SC2016,SC2046 -# REGENDATA ["--ghc-head","--apt=fftw3-dev","--installed=-all +deepseq","bash","messy.project","--sourcehut-source","https://example.org"] +# REGENDATA ["--ghc-head","--apt=fftw3-dev","--installed=-all +deepseq","bash","messy.project"] set -o pipefail diff --git a/fixtures/messy.github b/fixtures/messy.github index 8c34abe6..93be6624 100644 --- a/fixtures/messy.github +++ b/fixtures/messy.github @@ -2,7 +2,7 @@ # *INFO* Generating GitHub config for testing for GHC versions: ghc-head 7.8.1 7.8.2 7.8.3 7.8.4 7.10.1 7.10.2 7.10.3 8.0.1 8.0.2 8.2.1 8.2.2 8.4.1 8.4.2 8.4.3 8.4.4 8.6.1 8.6.2 8.6.3 8.6.4 8.6.5 8.8.1 8.8.2 8.8.3 8.8.4 8.10.1 8.10.2 8.10.3 8.10.4 8.10.5 8.10.6 8.10.7 # This GitHub workflow config has been generated by a script via # -# haskell-ci '--ghc-head' '--apt=fftw3-dev' '--installed=-all +deepseq' 'github' 'messy.project' '--sourcehut-source' 'https://example.org' +# haskell-ci '--ghc-head' '--apt=fftw3-dev' '--installed=-all +deepseq' 'github' 'messy.project' # # To regenerate the script (for example after adjusting tested-with) run # @@ -10,7 +10,7 @@ # # For more information, see https://github.com/haskell-CI/haskell-ci # -# REGENDATA ["--ghc-head","--apt=fftw3-dev","--installed=-all +deepseq","github","messy.project","--sourcehut-source","https://example.org"] +# REGENDATA ["--ghc-head","--apt=fftw3-dev","--installed=-all +deepseq","github","messy.project"] # name: Haskell-CI on: diff --git a/fixtures/messy.travis b/fixtures/messy.travis index 95aa78e0..31370e55 100644 --- a/fixtures/messy.travis +++ b/fixtures/messy.travis @@ -2,7 +2,7 @@ # *INFO* Generating Travis-CI config for testing for GHC versions: ghc-head 7.8.1 7.8.2 7.8.3 7.8.4 7.10.1 7.10.2 7.10.3 8.0.1 8.0.2 8.2.1 8.2.2 8.4.1 8.4.2 8.4.3 8.4.4 8.6.1 8.6.2 8.6.3 8.6.4 8.6.5 8.8.1 8.8.2 8.8.3 8.8.4 8.10.1 8.10.2 8.10.3 8.10.4 8.10.5 8.10.6 8.10.7 # This Travis job script has been generated by a script via # -# haskell-ci '--ghc-head' '--apt=fftw3-dev' '--installed=-all +deepseq' 'travis' 'messy.project' '--sourcehut-source' 'https://example.org' +# haskell-ci '--ghc-head' '--apt=fftw3-dev' '--installed=-all +deepseq' 'travis' 'messy.project' # # To regenerate the script (for example after adjusting tested-with) run # @@ -275,5 +275,5 @@ script: - rm -f cabal.project.local - ${CABAL} v2-build $WITHCOMPILER --disable-tests --disable-benchmarks all -# REGENDATA ["--ghc-head","--apt=fftw3-dev","--installed=-all +deepseq","travis","messy.project","--sourcehut-source","https://example.org"] +# REGENDATA ["--ghc-head","--apt=fftw3-dev","--installed=-all +deepseq","travis","messy.project"] # EOF diff --git a/fixtures/psql.bash b/fixtures/psql.bash index 602e8d3a..a53ea8e1 100644 --- a/fixtures/psql.bash +++ b/fixtures/psql.bash @@ -2,7 +2,7 @@ # *INFO* Generating Bash script for testing for GHC versions: 7.8.1 7.8.2 7.8.3 7.8.4 7.10.1 7.10.2 7.10.3 8.0.1 8.0.2 8.2.1 8.2.2 8.4.1 8.4.2 8.4.3 8.4.4 8.6.1 8.6.2 8.6.3 8.6.4 8.6.5 8.8.1 8.8.2 8.8.3 8.8.4 8.10.1 8.10.2 8.10.3 8.10.4 8.10.5 8.10.6 8.10.7 #!/bin/bash # shellcheck disable=SC2086,SC2016,SC2046 -# REGENDATA ["--postgresql","bash","psql.project","--sourcehut-source","https://example.org"] +# REGENDATA ["--postgresql","bash","psql.project"] set -o pipefail diff --git a/fixtures/psql.github b/fixtures/psql.github index 800ecb67..7f373ea5 100644 --- a/fixtures/psql.github +++ b/fixtures/psql.github @@ -2,7 +2,7 @@ # *INFO* Generating GitHub config for testing for GHC versions: 7.8.1 7.8.2 7.8.3 7.8.4 7.10.1 7.10.2 7.10.3 8.0.1 8.0.2 8.2.1 8.2.2 8.4.1 8.4.2 8.4.3 8.4.4 8.6.1 8.6.2 8.6.3 8.6.4 8.6.5 8.8.1 8.8.2 8.8.3 8.8.4 8.10.1 8.10.2 8.10.3 8.10.4 8.10.5 8.10.6 8.10.7 # This GitHub workflow config has been generated by a script via # -# haskell-ci '--postgresql' 'github' 'psql.project' '--sourcehut-source' 'https://example.org' +# haskell-ci '--postgresql' 'github' 'psql.project' # # To regenerate the script (for example after adjusting tested-with) run # @@ -10,7 +10,7 @@ # # For more information, see https://github.com/haskell-CI/haskell-ci # -# REGENDATA ["--postgresql","github","psql.project","--sourcehut-source","https://example.org"] +# REGENDATA ["--postgresql","github","psql.project"] # name: Haskell-CI on: diff --git a/fixtures/psql.travis b/fixtures/psql.travis index d65c70e7..d2386410 100644 --- a/fixtures/psql.travis +++ b/fixtures/psql.travis @@ -2,7 +2,7 @@ # *INFO* Generating Travis-CI config for testing for GHC versions: 7.8.1 7.8.2 7.8.3 7.8.4 7.10.1 7.10.2 7.10.3 8.0.1 8.0.2 8.2.1 8.2.2 8.4.1 8.4.2 8.4.3 8.4.4 8.6.1 8.6.2 8.6.3 8.6.4 8.6.5 8.8.1 8.8.2 8.8.3 8.8.4 8.10.1 8.10.2 8.10.3 8.10.4 8.10.5 8.10.6 8.10.7 # This Travis job script has been generated by a script via # -# haskell-ci '--postgresql' 'travis' 'psql.project' '--sourcehut-source' 'https://example.org' +# haskell-ci '--postgresql' 'travis' 'psql.project' # # To regenerate the script (for example after adjusting tested-with) run # @@ -227,5 +227,5 @@ script: - rm -f cabal.project.local - ${CABAL} v2-build $WITHCOMPILER --disable-tests --disable-benchmarks all -# REGENDATA ["--postgresql","travis","psql.project","--sourcehut-source","https://example.org"] +# REGENDATA ["--postgresql","travis","psql.project"] # EOF diff --git a/fixtures/sourcehut-parallel.bash b/fixtures/sourcehut-parallel.bash index b367120a..69dd2134 100644 --- a/fixtures/sourcehut-parallel.bash +++ b/fixtures/sourcehut-parallel.bash @@ -2,7 +2,7 @@ # *INFO* Generating Bash script for testing for GHC versions: 7.8.1 7.8.2 7.8.3 7.8.4 7.10.1 7.10.2 7.10.3 8.0.1 8.0.2 8.2.1 8.2.2 8.4.1 8.4.2 8.4.3 8.4.4 8.6.1 8.6.2 8.6.3 8.6.4 8.6.5 8.8.1 8.8.2 8.8.3 8.8.4 8.10.1 8.10.2 8.10.3 8.10.4 8.10.5 8.10.6 8.10.7 #!/bin/bash # shellcheck disable=SC2086,SC2016,SC2046 -# REGENDATA ["--sourcehut-parallel","bash","sourcehut-parallel.project","--sourcehut-source","https://example.org"] +# REGENDATA ["--sourcehut-parallel","bash","sourcehut-parallel.project"] set -o pipefail diff --git a/fixtures/sourcehut-parallel.github b/fixtures/sourcehut-parallel.github index eba63cae..57ef2ad9 100644 --- a/fixtures/sourcehut-parallel.github +++ b/fixtures/sourcehut-parallel.github @@ -2,7 +2,7 @@ # *INFO* Generating GitHub config for testing for GHC versions: 7.8.1 7.8.2 7.8.3 7.8.4 7.10.1 7.10.2 7.10.3 8.0.1 8.0.2 8.2.1 8.2.2 8.4.1 8.4.2 8.4.3 8.4.4 8.6.1 8.6.2 8.6.3 8.6.4 8.6.5 8.8.1 8.8.2 8.8.3 8.8.4 8.10.1 8.10.2 8.10.3 8.10.4 8.10.5 8.10.6 8.10.7 # This GitHub workflow config has been generated by a script via # -# haskell-ci '--sourcehut-parallel' 'github' 'sourcehut-parallel.project' '--sourcehut-source' 'https://example.org' +# haskell-ci '--sourcehut-parallel' 'github' 'sourcehut-parallel.project' # # To regenerate the script (for example after adjusting tested-with) run # @@ -10,7 +10,7 @@ # # For more information, see https://github.com/haskell-CI/haskell-ci # -# REGENDATA ["--sourcehut-parallel","github","sourcehut-parallel.project","--sourcehut-source","https://example.org"] +# REGENDATA ["--sourcehut-parallel","github","sourcehut-parallel.project"] # name: Haskell-CI on: diff --git a/fixtures/sourcehut-parallel.travis b/fixtures/sourcehut-parallel.travis index 1e4f25e6..4f6421a8 100644 --- a/fixtures/sourcehut-parallel.travis +++ b/fixtures/sourcehut-parallel.travis @@ -2,7 +2,7 @@ # *INFO* Generating Travis-CI config for testing for GHC versions: 7.8.1 7.8.2 7.8.3 7.8.4 7.10.1 7.10.2 7.10.3 8.0.1 8.0.2 8.2.1 8.2.2 8.4.1 8.4.2 8.4.3 8.4.4 8.6.1 8.6.2 8.6.3 8.6.4 8.6.5 8.8.1 8.8.2 8.8.3 8.8.4 8.10.1 8.10.2 8.10.3 8.10.4 8.10.5 8.10.6 8.10.7 # This Travis job script has been generated by a script via # -# haskell-ci '--sourcehut-parallel' 'travis' 'sourcehut-parallel.project' '--sourcehut-source' 'https://example.org' +# haskell-ci '--sourcehut-parallel' 'travis' 'sourcehut-parallel.project' # # To regenerate the script (for example after adjusting tested-with) run # @@ -223,5 +223,5 @@ script: - rm -f cabal.project.local - ${CABAL} v2-build $WITHCOMPILER --disable-tests --disable-benchmarks all -# REGENDATA ["--sourcehut-parallel","travis","sourcehut-parallel.project","--sourcehut-source","https://example.org"] +# REGENDATA ["--sourcehut-parallel","travis","sourcehut-parallel.project"] # EOF diff --git a/fixtures/travis-patch.bash b/fixtures/travis-patch.bash index d07891ad..2ab51386 100644 --- a/fixtures/travis-patch.bash +++ b/fixtures/travis-patch.bash @@ -2,7 +2,7 @@ # *INFO* Generating Bash script for testing for GHC versions: 7.8.1 7.8.2 7.8.3 7.8.4 7.10.1 7.10.2 7.10.3 8.0.1 8.0.2 8.2.1 8.2.2 8.4.1 8.4.2 8.4.3 8.4.4 8.6.1 8.6.2 8.6.3 8.6.4 8.6.5 8.8.1 8.8.2 8.8.3 8.8.4 8.10.1 8.10.2 8.10.3 8.10.4 8.10.5 8.10.6 8.10.7 #!/bin/bash # shellcheck disable=SC2086,SC2016,SC2046 -# REGENDATA ["--travis-patches=travis-patch.patch","bash","travis-patch.project","--sourcehut-source","https://example.org"] +# REGENDATA ["--travis-patches=travis-patch.patch","bash","travis-patch.project"] set -o pipefail diff --git a/fixtures/travis-patch.github b/fixtures/travis-patch.github index b2ead3fa..811504a4 100644 --- a/fixtures/travis-patch.github +++ b/fixtures/travis-patch.github @@ -2,7 +2,7 @@ # *INFO* Generating GitHub config for testing for GHC versions: 7.8.1 7.8.2 7.8.3 7.8.4 7.10.1 7.10.2 7.10.3 8.0.1 8.0.2 8.2.1 8.2.2 8.4.1 8.4.2 8.4.3 8.4.4 8.6.1 8.6.2 8.6.3 8.6.4 8.6.5 8.8.1 8.8.2 8.8.3 8.8.4 8.10.1 8.10.2 8.10.3 8.10.4 8.10.5 8.10.6 8.10.7 # This GitHub workflow config has been generated by a script via # -# haskell-ci '--travis-patches=travis-patch.patch' 'github' 'travis-patch.project' '--sourcehut-source' 'https://example.org' +# haskell-ci '--travis-patches=travis-patch.patch' 'github' 'travis-patch.project' # # To regenerate the script (for example after adjusting tested-with) run # @@ -10,7 +10,7 @@ # # For more information, see https://github.com/haskell-CI/haskell-ci # -# REGENDATA ["--travis-patches=travis-patch.patch","github","travis-patch.project","--sourcehut-source","https://example.org"] +# REGENDATA ["--travis-patches=travis-patch.patch","github","travis-patch.project"] # name: Haskell-CI on: diff --git a/fixtures/travis-patch.travis b/fixtures/travis-patch.travis index 2b90765f..8c1a7575 100644 --- a/fixtures/travis-patch.travis +++ b/fixtures/travis-patch.travis @@ -2,7 +2,7 @@ # *INFO* Generating Travis-CI config for testing for GHC versions: 7.8.1 7.8.2 7.8.3 7.8.4 7.10.1 7.10.2 7.10.3 8.0.1 8.0.2 8.2.1 8.2.2 8.4.1 8.4.2 8.4.3 8.4.4 8.6.1 8.6.2 8.6.3 8.6.4 8.6.5 8.8.1 8.8.2 8.8.3 8.8.4 8.10.1 8.10.2 8.10.3 8.10.4 8.10.5 8.10.6 8.10.7 # This Travis job script has been generated by a script via # -# haskell-ci '--travis-patches=travis-patch.patch' 'travis' 'travis-patch.project' '--sourcehut-source' 'https://example.org' +# haskell-ci '--travis-patches=travis-patch.patch' 'travis' 'travis-patch.project' # # To regenerate the script (for example after adjusting tested-with) run # @@ -223,5 +223,5 @@ script: - rm -f cabal.project.local - ${CABAL} v2-build $WITHCOMPILER --disable-tests --disable-benchmarks all -# REGENDATA ["--travis-patches=travis-patch.patch","travis","travis-patch.project","--sourcehut-source","https://example.org"] +# REGENDATA ["--travis-patches=travis-patch.patch","travis","travis-patch.project"] # EOF diff --git a/test/Tests.hs b/test/Tests.hs index d3055df5..3ce5cf4b 100644 --- a/test/Tests.hs +++ b/test/Tests.hs @@ -81,7 +81,9 @@ fixtureGoldenTest fp = testGroup fp makeFlags :: IO ([String], Options) makeFlags = do argv <- readArgv - let argv' = argv ++ [name, projectfp] ++ ["--sourcehut-source", "https://example.org"] + let argv' = argv ++ [name, projectfp] ++ + [ arg | arg <- ["--sourcehut-source", "https://example.org"] + , name == "sourcehut" ] (_fp, opts) <- parseOptions argv' return (argv', opts) From 4b1219da63bf491e49b7077176b17cc96810ab1a Mon Sep 17 00:00:00 2001 From: Francesco Gazzetta Date: Sun, 19 Dec 2021 19:30:53 +0100 Subject: [PATCH 20/23] hlint: ignore camelCase suggestion --- .hlint.yaml | 1 + 1 file changed, 1 insertion(+) diff --git a/.hlint.yaml b/.hlint.yaml index 7ddf4c14..90b71ebe 100644 --- a/.hlint.yaml +++ b/.hlint.yaml @@ -15,3 +15,4 @@ - ignore: {name: "Use <$>"} - ignore: {name: Reduce duplication} - ignore: {within: HaskellCI.Bash.Template} +- ignore: {name: Use camelCase} From 53c2225ca1df2f20a25f55d3742e6c9406232015 Mon Sep 17 00:00:00 2001 From: Francesco Gazzetta Date: Sun, 19 Dec 2021 19:31:11 +0100 Subject: [PATCH 21/23] sourcehut: fix hlint warning --- src/HaskellCI.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/src/HaskellCI.hs b/src/HaskellCI.hs index 976589bb..56f4c37b 100644 --- a/src/HaskellCI.hs +++ b/src/HaskellCI.hs @@ -421,8 +421,8 @@ sourcehutFromConfigFile args opts path = do let prj' | cfgGhcHead config = over (mapped . field @"pkgJobs") (S.insert GHCHead) prj | otherwise = prj - ls <- genSourcehutFromConfigs args config gitconfig prj' ghcs - return ls -- TODO patchSourcehut config ls + genSourcehutFromConfigs args config gitconfig prj' ghcs + -- TODO ls <- genSourcehutFromConfigs ...; patchSourcehut config ls genSourcehutFromConfigs :: (Monad m, MonadIO m, MonadDiagnostics m) From df60344b5dddfcf2e11b9afa534c3a8b272e0a7f Mon Sep 17 00:00:00 2001 From: Francesco Gazzetta Date: Fri, 3 Jun 2022 15:04:27 +0200 Subject: [PATCH 22/23] fixup! sourcehut: add golden tests --- fixtures/all-versions.sourcehut | 82 +++++++++++++++++++++++++++++- fixtures/enabled-jobs.sourcehut | 82 +++++++++++++++++++++++++++++- fixtures/sourcehut-parallel.bash | 2 +- fixtures/sourcehut-parallel.github | 8 +-- fixtures/sourcehut-parallel.travis | 2 +- 5 files changed, 168 insertions(+), 8 deletions(-) diff --git a/fixtures/all-versions.sourcehut b/fixtures/all-versions.sourcehut index f843761d..fc32afd9 100644 --- a/fixtures/all-versions.sourcehut +++ b/fixtures/all-versions.sourcehut @@ -1,5 +1,5 @@ # SUCCESS -# *INFO* Generating Sourcehut config for testing for GHC versions: 7.0.1 7.0.2 7.0.3 7.0.4 7.2.1 7.2.2 7.4.1 7.4.2 7.6.1 7.6.2 7.6.3 7.8.1 7.8.2 7.8.3 7.8.4 7.10.1 7.10.2 7.10.3 8.0.1 8.0.2 8.2.1 8.2.2 8.4.1 8.4.2 8.4.3 8.4.4 8.6.1 8.6.2 8.6.3 8.6.4 8.6.5 8.8.1 8.8.2 8.8.3 8.8.4 8.10.1 8.10.2 8.10.3 8.10.4 8.10.5 8.10.6 8.10.7 9.0.1 9.2.1 ghcjs-8.4 +# *INFO* Generating Sourcehut config for testing for GHC versions: 7.0.1 7.0.2 7.0.3 7.0.4 7.2.1 7.2.2 7.4.1 7.4.2 7.6.1 7.6.2 7.6.3 7.8.1 7.8.2 7.8.3 7.8.4 7.10.1 7.10.2 7.10.3 8.0.1 8.0.2 8.2.1 8.2.2 8.4.1 8.4.2 8.4.3 8.4.4 8.6.1 8.6.2 8.6.3 8.6.4 8.6.5 8.8.1 8.8.2 8.8.3 8.8.4 8.10.1 8.10.2 8.10.3 8.10.4 8.10.5 8.10.6 8.10.7 9.0.1 9.0.2 9.2.1 9.2.2 9.2.3 9.4.1 ghcjs-8.4 # manifest name: all # This Sourcehut job script has been generated by a script via # @@ -60,7 +60,11 @@ packages: - ghc-8.10.6 - ghc-8.10.7 - ghc-9.0.1 + - ghc-9.0.2 - ghc-9.2.1 + - ghc-9.2.2 + - ghc-9.2.3 + - ghc-9.4.1 - ghcjs-8.4 repositories: hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 @@ -888,6 +892,25 @@ tasks: - 9_0_1-haddock: | cd example.org cabal haddock all + - 9_0_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-9.0.2 + - 9_0_2-check: | + cd example.org + cabal check + - 9_0_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 9_0_2-build: | + cd example.org + cabal build all + - 9_0_2-test: | + cd example.org + cabal test all --enable-tests + - 9_0_2-haddock: | + cd example.org + cabal haddock all - 9_2_1-prepare: | cd example.org cabal configure -w /opt/ghc/bin/ghc-9.2.1 @@ -907,6 +930,63 @@ tasks: - 9_2_1-haddock: | cd example.org cabal haddock all + - 9_2_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-9.2.2 + - 9_2_2-check: | + cd example.org + cabal check + - 9_2_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 9_2_2-build: | + cd example.org + cabal build all + - 9_2_2-test: | + cd example.org + cabal test all --enable-tests + - 9_2_2-haddock: | + cd example.org + cabal haddock all + - 9_2_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-9.2.3 + - 9_2_3-check: | + cd example.org + cabal check + - 9_2_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 9_2_3-build: | + cd example.org + cabal build all + - 9_2_3-test: | + cd example.org + cabal test all --enable-tests + - 9_2_3-haddock: | + cd example.org + cabal haddock all + - 9_4_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-9.4.1 + - 9_4_1-check: | + cd example.org + cabal check + - 9_4_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 9_4_1-build: | + cd example.org + cabal build all + - 9_4_1-test: | + cd example.org + cabal test all --enable-tests + - 9_4_1-haddock: | + cd example.org + cabal haddock all - ghcjs-8_4-prepare: | cd example.org cabal configure -w /opt/ghc/bin/ghcjs-8.4 diff --git a/fixtures/enabled-jobs.sourcehut b/fixtures/enabled-jobs.sourcehut index e8753cee..851862bb 100644 --- a/fixtures/enabled-jobs.sourcehut +++ b/fixtures/enabled-jobs.sourcehut @@ -1,5 +1,5 @@ # SUCCESS -# *INFO* Generating Sourcehut config for testing for GHC versions: 8.0.1 8.0.2 8.2.1 8.2.2 8.4.1 8.4.2 8.4.3 8.4.4 8.6.1 8.6.2 8.6.3 8.6.4 8.6.5 8.8.1 8.8.2 8.8.3 8.8.4 8.10.1 8.10.2 8.10.3 8.10.4 8.10.5 8.10.6 8.10.7 9.0.1 9.2.1 ghcjs-8.4 +# *INFO* Generating Sourcehut config for testing for GHC versions: 8.0.1 8.0.2 8.2.1 8.2.2 8.4.1 8.4.2 8.4.3 8.4.4 8.6.1 8.6.2 8.6.3 8.6.4 8.6.5 8.8.1 8.8.2 8.8.3 8.8.4 8.10.1 8.10.2 8.10.3 8.10.4 8.10.5 8.10.6 8.10.7 9.0.1 9.0.2 9.2.1 9.2.2 9.2.3 9.4.1 ghcjs-8.4 # manifest name: all # This Sourcehut job script has been generated by a script via # @@ -42,7 +42,11 @@ packages: - ghc-8.10.6 - ghc-8.10.7 - ghc-9.0.1 + - ghc-9.0.2 - ghc-9.2.1 + - ghc-9.2.2 + - ghc-9.2.3 + - ghc-9.4.1 - ghcjs-8.4 repositories: hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 @@ -528,6 +532,25 @@ tasks: - 9_0_1-haddock: | cd example.org cabal haddock all + - 9_0_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-9.0.2 + - 9_0_2-check: | + cd example.org + cabal check + - 9_0_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 9_0_2-build: | + cd example.org + cabal build all + - 9_0_2-test: | + cd example.org + cabal test all --enable-tests + - 9_0_2-haddock: | + cd example.org + cabal haddock all - 9_2_1-prepare: | cd example.org cabal configure -w /opt/ghc/bin/ghc-9.2.1 @@ -547,6 +570,63 @@ tasks: - 9_2_1-haddock: | cd example.org cabal haddock all + - 9_2_2-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-9.2.2 + - 9_2_2-check: | + cd example.org + cabal check + - 9_2_2-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 9_2_2-build: | + cd example.org + cabal build all + - 9_2_2-test: | + cd example.org + cabal test all --enable-tests + - 9_2_2-haddock: | + cd example.org + cabal haddock all + - 9_2_3-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-9.2.3 + - 9_2_3-check: | + cd example.org + cabal check + - 9_2_3-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 9_2_3-build: | + cd example.org + cabal build all + - 9_2_3-test: | + cd example.org + cabal test all --enable-tests + - 9_2_3-haddock: | + cd example.org + cabal haddock all + - 9_4_1-prepare: | + cd example.org + cabal configure -w /opt/ghc/bin/ghc-9.4.1 + - 9_4_1-check: | + cd example.org + cabal check + - 9_4_1-dependencies: | + cd example.org + cabal build all --enable-tests --only-dependencies + cabal build all --only-dependencies + - 9_4_1-build: | + cd example.org + cabal build all + - 9_4_1-test: | + cd example.org + cabal test all --enable-tests + - 9_4_1-haddock: | + cd example.org + cabal haddock all - ghcjs-8_4-prepare: | cd example.org cabal configure -w /opt/ghc/bin/ghcjs-8.4 diff --git a/fixtures/sourcehut-parallel.bash b/fixtures/sourcehut-parallel.bash index 69dd2134..00e669e3 100644 --- a/fixtures/sourcehut-parallel.bash +++ b/fixtures/sourcehut-parallel.bash @@ -508,7 +508,7 @@ change_dir "$BUILDDIR" # haddock put_info "haddock" -run_cmd $CABAL v2-haddock $ARG_COMPILER --with-haddock $HADDOCK $ARG_TESTS $ARG_BENCH all +run_cmd $CABAL v2-haddock --haddock-all $ARG_COMPILER --with-haddock $HADDOCK $ARG_TESTS $ARG_BENCH all # unconstrained build put_info "unconstrained build" diff --git a/fixtures/sourcehut-parallel.github b/fixtures/sourcehut-parallel.github index 57ef2ad9..52cfc786 100644 --- a/fixtures/sourcehut-parallel.github +++ b/fixtures/sourcehut-parallel.github @@ -19,7 +19,7 @@ on: jobs: linux: name: Haskell-CI - Linux - ${{ matrix.compiler }} - runs-on: ubuntu-18.04 + runs-on: ubuntu-20.04 timeout-minutes: 60 container: @@ -191,7 +191,7 @@ jobs: apt-get install -y --no-install-recommends gnupg ca-certificates dirmngr curl git software-properties-common libtinfo5 if [ "${{ matrix.setup-method }}" = ghcup ]; then mkdir -p "$HOME/.ghcup/bin" - curl -sL https://downloads.haskell.org/ghcup/0.1.17.3/x86_64-linux-ghcup-0.1.17.3 > "$HOME/.ghcup/bin/ghcup" + curl -sL https://downloads.haskell.org/ghcup/0.1.17.8/x86_64-linux-ghcup-0.1.17.8 > "$HOME/.ghcup/bin/ghcup" chmod a+x "$HOME/.ghcup/bin/ghcup" "$HOME/.ghcup/bin/ghcup" install ghc "$HCVER" "$HOME/.ghcup/bin/ghcup" install cabal 3.6.2.0 @@ -200,7 +200,7 @@ jobs: apt-get update apt-get install -y "$HCNAME" mkdir -p "$HOME/.ghcup/bin" - curl -sL https://downloads.haskell.org/ghcup/0.1.17.3/x86_64-linux-ghcup-0.1.17.3 > "$HOME/.ghcup/bin/ghcup" + curl -sL https://downloads.haskell.org/ghcup/0.1.17.8/x86_64-linux-ghcup-0.1.17.8 > "$HOME/.ghcup/bin/ghcup" chmod a+x "$HOME/.ghcup/bin/ghcup" "$HOME/.ghcup/bin/ghcup" install cabal 3.6.2.0 fi @@ -345,7 +345,7 @@ jobs: ${CABAL} -vnormal check - name: haddock run: | - $CABAL v2-haddock $ARG_COMPILER --with-haddock $HADDOCK $ARG_TESTS $ARG_BENCH all + $CABAL v2-haddock --haddock-all $ARG_COMPILER --with-haddock $HADDOCK $ARG_TESTS $ARG_BENCH all - name: unconstrained build run: | rm -f cabal.project.local diff --git a/fixtures/sourcehut-parallel.travis b/fixtures/sourcehut-parallel.travis index 4f6421a8..61f08c45 100644 --- a/fixtures/sourcehut-parallel.travis +++ b/fixtures/sourcehut-parallel.travis @@ -218,7 +218,7 @@ script: # cabal check... - (cd ${PKGDIR_servant} && ${CABAL} -vnormal check) # haddock... - - ${CABAL} v2-haddock $WITHCOMPILER --with-haddock $HADDOCK ${TEST} ${BENCH} all + - ${CABAL} v2-haddock --haddock-all $WITHCOMPILER --with-haddock $HADDOCK ${TEST} ${BENCH} all # Building without installed constraints for packages in global-db... - rm -f cabal.project.local - ${CABAL} v2-build $WITHCOMPILER --disable-tests --disable-benchmarks all From d08d6bf02fc00609853f1ba09f8f3dcb1e6640ff Mon Sep 17 00:00:00 2001 From: Francesco Gazzetta Date: Fri, 3 Jun 2022 16:52:25 +0200 Subject: [PATCH 23/23] sourcehut: add ghcup support --- fixtures/all-versions.sourcehut | 126 ++++---- fixtures/copy-fields-all.sourcehut | 80 ++--- fixtures/copy-fields-none.sourcehut | 80 ++--- fixtures/copy-fields-some.sourcehut | 80 ++--- fixtures/empty-line.sourcehut | 84 ++--- fixtures/enabled-jobs.sourcehut | 90 +++--- fixtures/irc-channels.sourcehut | 80 ++--- fixtures/messy.sourcehut | 86 ++--- fixtures/psql.sourcehut | 80 ++--- fixtures/sourcehut-parallel.sourcehut | 440 ++++++++++++++++++-------- fixtures/travis-patch.sourcehut | 80 ++--- src/HaskellCI/Sourcehut.hs | 47 ++- 12 files changed, 810 insertions(+), 543 deletions(-) diff --git a/fixtures/all-versions.sourcehut b/fixtures/all-versions.sourcehut index fc32afd9..90dc202b 100644 --- a/fixtures/all-versions.sourcehut +++ b/fixtures/all-versions.sourcehut @@ -16,7 +16,7 @@ image: ubuntu/bionic packages: - gcc - - cabal-install-3.4 + - libgmp-dev - ghc-7.0.1 - ghc-7.0.2 - ghc-7.0.3 @@ -56,15 +56,7 @@ packages: - ghc-8.10.2 - ghc-8.10.3 - ghc-8.10.4 - - ghc-8.10.5 - - ghc-8.10.6 - - ghc-8.10.7 - ghc-9.0.1 - - ghc-9.0.2 - - ghc-9.2.1 - - ghc-9.2.2 - - ghc-9.2.3 - - ghc-9.4.1 - ghcjs-8.4 repositories: hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 @@ -72,12 +64,26 @@ sources: - https://example.org tasks: - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + mkdir -p "$HOME/.ghcup/bin" + curl -sL https://downloads.haskell.org/ghcup/0.1.17.8/x86_64-linux-ghcup-0.1.17.8 > "$HOME/.ghcup/bin/ghcup" + chmod a+x "$HOME/.ghcup/bin/ghcup" + export PATH=$PATH:$HOME/.ghcup/bin + echo "export PATH=$PATH:$HOME/.ghcup/bin" >> ~/.buildenv + "$HOME/.ghcup/bin/ghcup" install cabal 3.6 + "$HOME/.ghcup/bin/ghcup" install ghc "ghc-8.10.5" + "$HOME/.ghcup/bin/ghcup" install ghc "ghc-8.10.6" + "$HOME/.ghcup/bin/ghcup" install ghc "ghc-8.10.7" + "$HOME/.ghcup/bin/ghcup" install ghc "ghc-9.0.2" + "$HOME/.ghcup/bin/ghcup" install ghc "ghc-9.2.1" + "$HOME/.ghcup/bin/ghcup" install ghc "ghc-9.2.2" + "$HOME/.ghcup/bin/ghcup" install ghc "ghc-9.2.3" + "$HOME/.ghcup/bin/ghcup" install ghc "ghc-9.4.1" + export PATH=$PATH:/opt/ghc/bin + echo "export PATH=$PATH:/opt/ghc/bin" >> ~/.buildenv cabal update - 7_0_1-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.0.1 + cabal configure -w ghc-7.0.1 - 7_0_1-check: | cd example.org cabal check @@ -96,7 +102,7 @@ tasks: cabal haddock all - 7_0_2-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.0.2 + cabal configure -w ghc-7.0.2 - 7_0_2-check: | cd example.org cabal check @@ -115,7 +121,7 @@ tasks: cabal haddock all - 7_0_3-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.0.3 + cabal configure -w ghc-7.0.3 - 7_0_3-check: | cd example.org cabal check @@ -134,7 +140,7 @@ tasks: cabal haddock all - 7_0_4-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.0.4 + cabal configure -w ghc-7.0.4 - 7_0_4-check: | cd example.org cabal check @@ -153,7 +159,7 @@ tasks: cabal haddock all - 7_2_1-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.2.1 + cabal configure -w ghc-7.2.1 - 7_2_1-check: | cd example.org cabal check @@ -172,7 +178,7 @@ tasks: cabal haddock all - 7_2_2-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.2.2 + cabal configure -w ghc-7.2.2 - 7_2_2-check: | cd example.org cabal check @@ -191,7 +197,7 @@ tasks: cabal haddock all - 7_4_1-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.4.1 + cabal configure -w ghc-7.4.1 - 7_4_1-check: | cd example.org cabal check @@ -210,7 +216,7 @@ tasks: cabal haddock all - 7_4_2-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.4.2 + cabal configure -w ghc-7.4.2 - 7_4_2-check: | cd example.org cabal check @@ -229,7 +235,7 @@ tasks: cabal haddock all - 7_6_1-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.6.1 + cabal configure -w ghc-7.6.1 - 7_6_1-check: | cd example.org cabal check @@ -248,7 +254,7 @@ tasks: cabal haddock all - 7_6_2-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.6.2 + cabal configure -w ghc-7.6.2 - 7_6_2-check: | cd example.org cabal check @@ -267,7 +273,7 @@ tasks: cabal haddock all - 7_6_3-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.6.3 + cabal configure -w ghc-7.6.3 - 7_6_3-check: | cd example.org cabal check @@ -286,7 +292,7 @@ tasks: cabal haddock all - 7_8_1-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.8.1 + cabal configure -w ghc-7.8.1 - 7_8_1-check: | cd example.org cabal check @@ -305,7 +311,7 @@ tasks: cabal haddock all - 7_8_2-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.8.2 + cabal configure -w ghc-7.8.2 - 7_8_2-check: | cd example.org cabal check @@ -324,7 +330,7 @@ tasks: cabal haddock all - 7_8_3-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.8.3 + cabal configure -w ghc-7.8.3 - 7_8_3-check: | cd example.org cabal check @@ -343,7 +349,7 @@ tasks: cabal haddock all - 7_8_4-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.8.4 + cabal configure -w ghc-7.8.4 - 7_8_4-check: | cd example.org cabal check @@ -362,7 +368,7 @@ tasks: cabal haddock all - 7_10_1-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.10.1 + cabal configure -w ghc-7.10.1 - 7_10_1-check: | cd example.org cabal check @@ -381,7 +387,7 @@ tasks: cabal haddock all - 7_10_2-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.10.2 + cabal configure -w ghc-7.10.2 - 7_10_2-check: | cd example.org cabal check @@ -400,7 +406,7 @@ tasks: cabal haddock all - 7_10_3-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.10.3 + cabal configure -w ghc-7.10.3 - 7_10_3-check: | cd example.org cabal check @@ -419,7 +425,7 @@ tasks: cabal haddock all - 8_0_1-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.0.1 + cabal configure -w ghc-8.0.1 - 8_0_1-check: | cd example.org cabal check @@ -438,7 +444,7 @@ tasks: cabal haddock all - 8_0_2-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.0.2 + cabal configure -w ghc-8.0.2 - 8_0_2-check: | cd example.org cabal check @@ -457,7 +463,7 @@ tasks: cabal haddock all - 8_2_1-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.2.1 + cabal configure -w ghc-8.2.1 - 8_2_1-check: | cd example.org cabal check @@ -476,7 +482,7 @@ tasks: cabal haddock all - 8_2_2-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.2.2 + cabal configure -w ghc-8.2.2 - 8_2_2-check: | cd example.org cabal check @@ -495,7 +501,7 @@ tasks: cabal haddock all - 8_4_1-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.4.1 + cabal configure -w ghc-8.4.1 - 8_4_1-check: | cd example.org cabal check @@ -514,7 +520,7 @@ tasks: cabal haddock all - 8_4_2-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.4.2 + cabal configure -w ghc-8.4.2 - 8_4_2-check: | cd example.org cabal check @@ -533,7 +539,7 @@ tasks: cabal haddock all - 8_4_3-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.4.3 + cabal configure -w ghc-8.4.3 - 8_4_3-check: | cd example.org cabal check @@ -552,7 +558,7 @@ tasks: cabal haddock all - 8_4_4-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.4.4 + cabal configure -w ghc-8.4.4 - 8_4_4-check: | cd example.org cabal check @@ -571,7 +577,7 @@ tasks: cabal haddock all - 8_6_1-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.6.1 + cabal configure -w ghc-8.6.1 - 8_6_1-check: | cd example.org cabal check @@ -590,7 +596,7 @@ tasks: cabal haddock all - 8_6_2-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.6.2 + cabal configure -w ghc-8.6.2 - 8_6_2-check: | cd example.org cabal check @@ -609,7 +615,7 @@ tasks: cabal haddock all - 8_6_3-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.6.3 + cabal configure -w ghc-8.6.3 - 8_6_3-check: | cd example.org cabal check @@ -628,7 +634,7 @@ tasks: cabal haddock all - 8_6_4-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.6.4 + cabal configure -w ghc-8.6.4 - 8_6_4-check: | cd example.org cabal check @@ -647,7 +653,7 @@ tasks: cabal haddock all - 8_6_5-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.6.5 + cabal configure -w ghc-8.6.5 - 8_6_5-check: | cd example.org cabal check @@ -666,7 +672,7 @@ tasks: cabal haddock all - 8_8_1-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.8.1 + cabal configure -w ghc-8.8.1 - 8_8_1-check: | cd example.org cabal check @@ -685,7 +691,7 @@ tasks: cabal haddock all - 8_8_2-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.8.2 + cabal configure -w ghc-8.8.2 - 8_8_2-check: | cd example.org cabal check @@ -704,7 +710,7 @@ tasks: cabal haddock all - 8_8_3-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.8.3 + cabal configure -w ghc-8.8.3 - 8_8_3-check: | cd example.org cabal check @@ -723,7 +729,7 @@ tasks: cabal haddock all - 8_8_4-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.8.4 + cabal configure -w ghc-8.8.4 - 8_8_4-check: | cd example.org cabal check @@ -742,7 +748,7 @@ tasks: cabal haddock all - 8_10_1-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.1 + cabal configure -w ghc-8.10.1 - 8_10_1-check: | cd example.org cabal check @@ -761,7 +767,7 @@ tasks: cabal haddock all - 8_10_2-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.2 + cabal configure -w ghc-8.10.2 - 8_10_2-check: | cd example.org cabal check @@ -780,7 +786,7 @@ tasks: cabal haddock all - 8_10_3-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.3 + cabal configure -w ghc-8.10.3 - 8_10_3-check: | cd example.org cabal check @@ -799,7 +805,7 @@ tasks: cabal haddock all - 8_10_4-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.4 + cabal configure -w ghc-8.10.4 - 8_10_4-check: | cd example.org cabal check @@ -818,7 +824,7 @@ tasks: cabal haddock all - 8_10_5-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.5 + cabal configure -w ghc-8.10.5 - 8_10_5-check: | cd example.org cabal check @@ -837,7 +843,7 @@ tasks: cabal haddock all - 8_10_6-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.6 + cabal configure -w ghc-8.10.6 - 8_10_6-check: | cd example.org cabal check @@ -856,7 +862,7 @@ tasks: cabal haddock all - 8_10_7-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.7 + cabal configure -w ghc-8.10.7 - 8_10_7-check: | cd example.org cabal check @@ -875,7 +881,7 @@ tasks: cabal haddock all - 9_0_1-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-9.0.1 + cabal configure -w ghc-9.0.1 - 9_0_1-check: | cd example.org cabal check @@ -894,7 +900,7 @@ tasks: cabal haddock all - 9_0_2-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-9.0.2 + cabal configure -w ghc-9.0.2 - 9_0_2-check: | cd example.org cabal check @@ -913,7 +919,7 @@ tasks: cabal haddock all - 9_2_1-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-9.2.1 + cabal configure -w ghc-9.2.1 - 9_2_1-check: | cd example.org cabal check @@ -932,7 +938,7 @@ tasks: cabal haddock all - 9_2_2-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-9.2.2 + cabal configure -w ghc-9.2.2 - 9_2_2-check: | cd example.org cabal check @@ -951,7 +957,7 @@ tasks: cabal haddock all - 9_2_3-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-9.2.3 + cabal configure -w ghc-9.2.3 - 9_2_3-check: | cd example.org cabal check @@ -970,7 +976,7 @@ tasks: cabal haddock all - 9_4_1-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-9.4.1 + cabal configure -w ghc-9.4.1 - 9_4_1-check: | cd example.org cabal check @@ -989,7 +995,7 @@ tasks: cabal haddock all - ghcjs-8_4-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghcjs-8.4 + cabal configure -w ghcjs-8.4 - ghcjs-8_4-check: | cd example.org cabal check diff --git a/fixtures/copy-fields-all.sourcehut b/fixtures/copy-fields-all.sourcehut index aaa0198c..1ccea425 100644 --- a/fixtures/copy-fields-all.sourcehut +++ b/fixtures/copy-fields-all.sourcehut @@ -16,7 +16,7 @@ image: ubuntu/bionic packages: - gcc - - cabal-install-3.4 + - libgmp-dev - ghc-7.8.1 - ghc-7.8.2 - ghc-7.8.3 @@ -45,21 +45,27 @@ packages: - ghc-8.10.2 - ghc-8.10.3 - ghc-8.10.4 - - ghc-8.10.5 - - ghc-8.10.6 - - ghc-8.10.7 repositories: hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 sources: - https://example.org tasks: - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + mkdir -p "$HOME/.ghcup/bin" + curl -sL https://downloads.haskell.org/ghcup/0.1.17.8/x86_64-linux-ghcup-0.1.17.8 > "$HOME/.ghcup/bin/ghcup" + chmod a+x "$HOME/.ghcup/bin/ghcup" + export PATH=$PATH:$HOME/.ghcup/bin + echo "export PATH=$PATH:$HOME/.ghcup/bin" >> ~/.buildenv + "$HOME/.ghcup/bin/ghcup" install cabal 3.6 + "$HOME/.ghcup/bin/ghcup" install ghc "ghc-8.10.5" + "$HOME/.ghcup/bin/ghcup" install ghc "ghc-8.10.6" + "$HOME/.ghcup/bin/ghcup" install ghc "ghc-8.10.7" + export PATH=$PATH:/opt/ghc/bin + echo "export PATH=$PATH:/opt/ghc/bin" >> ~/.buildenv cabal update - 7_8_1-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.8.1 + cabal configure -w ghc-7.8.1 - 7_8_1-check: | cd example.org cabal check @@ -78,7 +84,7 @@ tasks: cabal haddock all - 7_8_2-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.8.2 + cabal configure -w ghc-7.8.2 - 7_8_2-check: | cd example.org cabal check @@ -97,7 +103,7 @@ tasks: cabal haddock all - 7_8_3-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.8.3 + cabal configure -w ghc-7.8.3 - 7_8_3-check: | cd example.org cabal check @@ -116,7 +122,7 @@ tasks: cabal haddock all - 7_8_4-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.8.4 + cabal configure -w ghc-7.8.4 - 7_8_4-check: | cd example.org cabal check @@ -135,7 +141,7 @@ tasks: cabal haddock all - 7_10_1-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.10.1 + cabal configure -w ghc-7.10.1 - 7_10_1-check: | cd example.org cabal check @@ -154,7 +160,7 @@ tasks: cabal haddock all - 7_10_2-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.10.2 + cabal configure -w ghc-7.10.2 - 7_10_2-check: | cd example.org cabal check @@ -173,7 +179,7 @@ tasks: cabal haddock all - 7_10_3-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.10.3 + cabal configure -w ghc-7.10.3 - 7_10_3-check: | cd example.org cabal check @@ -192,7 +198,7 @@ tasks: cabal haddock all - 8_0_1-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.0.1 + cabal configure -w ghc-8.0.1 - 8_0_1-check: | cd example.org cabal check @@ -211,7 +217,7 @@ tasks: cabal haddock all - 8_0_2-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.0.2 + cabal configure -w ghc-8.0.2 - 8_0_2-check: | cd example.org cabal check @@ -230,7 +236,7 @@ tasks: cabal haddock all - 8_2_1-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.2.1 + cabal configure -w ghc-8.2.1 - 8_2_1-check: | cd example.org cabal check @@ -249,7 +255,7 @@ tasks: cabal haddock all - 8_2_2-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.2.2 + cabal configure -w ghc-8.2.2 - 8_2_2-check: | cd example.org cabal check @@ -268,7 +274,7 @@ tasks: cabal haddock all - 8_4_1-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.4.1 + cabal configure -w ghc-8.4.1 - 8_4_1-check: | cd example.org cabal check @@ -287,7 +293,7 @@ tasks: cabal haddock all - 8_4_2-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.4.2 + cabal configure -w ghc-8.4.2 - 8_4_2-check: | cd example.org cabal check @@ -306,7 +312,7 @@ tasks: cabal haddock all - 8_4_3-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.4.3 + cabal configure -w ghc-8.4.3 - 8_4_3-check: | cd example.org cabal check @@ -325,7 +331,7 @@ tasks: cabal haddock all - 8_4_4-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.4.4 + cabal configure -w ghc-8.4.4 - 8_4_4-check: | cd example.org cabal check @@ -344,7 +350,7 @@ tasks: cabal haddock all - 8_6_1-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.6.1 + cabal configure -w ghc-8.6.1 - 8_6_1-check: | cd example.org cabal check @@ -363,7 +369,7 @@ tasks: cabal haddock all - 8_6_2-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.6.2 + cabal configure -w ghc-8.6.2 - 8_6_2-check: | cd example.org cabal check @@ -382,7 +388,7 @@ tasks: cabal haddock all - 8_6_3-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.6.3 + cabal configure -w ghc-8.6.3 - 8_6_3-check: | cd example.org cabal check @@ -401,7 +407,7 @@ tasks: cabal haddock all - 8_6_4-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.6.4 + cabal configure -w ghc-8.6.4 - 8_6_4-check: | cd example.org cabal check @@ -420,7 +426,7 @@ tasks: cabal haddock all - 8_6_5-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.6.5 + cabal configure -w ghc-8.6.5 - 8_6_5-check: | cd example.org cabal check @@ -439,7 +445,7 @@ tasks: cabal haddock all - 8_8_1-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.8.1 + cabal configure -w ghc-8.8.1 - 8_8_1-check: | cd example.org cabal check @@ -458,7 +464,7 @@ tasks: cabal haddock all - 8_8_2-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.8.2 + cabal configure -w ghc-8.8.2 - 8_8_2-check: | cd example.org cabal check @@ -477,7 +483,7 @@ tasks: cabal haddock all - 8_8_3-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.8.3 + cabal configure -w ghc-8.8.3 - 8_8_3-check: | cd example.org cabal check @@ -496,7 +502,7 @@ tasks: cabal haddock all - 8_8_4-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.8.4 + cabal configure -w ghc-8.8.4 - 8_8_4-check: | cd example.org cabal check @@ -515,7 +521,7 @@ tasks: cabal haddock all - 8_10_1-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.1 + cabal configure -w ghc-8.10.1 - 8_10_1-check: | cd example.org cabal check @@ -534,7 +540,7 @@ tasks: cabal haddock all - 8_10_2-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.2 + cabal configure -w ghc-8.10.2 - 8_10_2-check: | cd example.org cabal check @@ -553,7 +559,7 @@ tasks: cabal haddock all - 8_10_3-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.3 + cabal configure -w ghc-8.10.3 - 8_10_3-check: | cd example.org cabal check @@ -572,7 +578,7 @@ tasks: cabal haddock all - 8_10_4-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.4 + cabal configure -w ghc-8.10.4 - 8_10_4-check: | cd example.org cabal check @@ -591,7 +597,7 @@ tasks: cabal haddock all - 8_10_5-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.5 + cabal configure -w ghc-8.10.5 - 8_10_5-check: | cd example.org cabal check @@ -610,7 +616,7 @@ tasks: cabal haddock all - 8_10_6-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.6 + cabal configure -w ghc-8.10.6 - 8_10_6-check: | cd example.org cabal check @@ -629,7 +635,7 @@ tasks: cabal haddock all - 8_10_7-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.7 + cabal configure -w ghc-8.10.7 - 8_10_7-check: | cd example.org cabal check diff --git a/fixtures/copy-fields-none.sourcehut b/fixtures/copy-fields-none.sourcehut index eb3356c9..e68f043d 100644 --- a/fixtures/copy-fields-none.sourcehut +++ b/fixtures/copy-fields-none.sourcehut @@ -16,7 +16,7 @@ image: ubuntu/bionic packages: - gcc - - cabal-install-3.4 + - libgmp-dev - ghc-7.8.1 - ghc-7.8.2 - ghc-7.8.3 @@ -45,21 +45,27 @@ packages: - ghc-8.10.2 - ghc-8.10.3 - ghc-8.10.4 - - ghc-8.10.5 - - ghc-8.10.6 - - ghc-8.10.7 repositories: hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 sources: - https://example.org tasks: - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + mkdir -p "$HOME/.ghcup/bin" + curl -sL https://downloads.haskell.org/ghcup/0.1.17.8/x86_64-linux-ghcup-0.1.17.8 > "$HOME/.ghcup/bin/ghcup" + chmod a+x "$HOME/.ghcup/bin/ghcup" + export PATH=$PATH:$HOME/.ghcup/bin + echo "export PATH=$PATH:$HOME/.ghcup/bin" >> ~/.buildenv + "$HOME/.ghcup/bin/ghcup" install cabal 3.6 + "$HOME/.ghcup/bin/ghcup" install ghc "ghc-8.10.5" + "$HOME/.ghcup/bin/ghcup" install ghc "ghc-8.10.6" + "$HOME/.ghcup/bin/ghcup" install ghc "ghc-8.10.7" + export PATH=$PATH:/opt/ghc/bin + echo "export PATH=$PATH:/opt/ghc/bin" >> ~/.buildenv cabal update - 7_8_1-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.8.1 + cabal configure -w ghc-7.8.1 - 7_8_1-check: | cd example.org cabal check @@ -78,7 +84,7 @@ tasks: cabal haddock all - 7_8_2-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.8.2 + cabal configure -w ghc-7.8.2 - 7_8_2-check: | cd example.org cabal check @@ -97,7 +103,7 @@ tasks: cabal haddock all - 7_8_3-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.8.3 + cabal configure -w ghc-7.8.3 - 7_8_3-check: | cd example.org cabal check @@ -116,7 +122,7 @@ tasks: cabal haddock all - 7_8_4-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.8.4 + cabal configure -w ghc-7.8.4 - 7_8_4-check: | cd example.org cabal check @@ -135,7 +141,7 @@ tasks: cabal haddock all - 7_10_1-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.10.1 + cabal configure -w ghc-7.10.1 - 7_10_1-check: | cd example.org cabal check @@ -154,7 +160,7 @@ tasks: cabal haddock all - 7_10_2-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.10.2 + cabal configure -w ghc-7.10.2 - 7_10_2-check: | cd example.org cabal check @@ -173,7 +179,7 @@ tasks: cabal haddock all - 7_10_3-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.10.3 + cabal configure -w ghc-7.10.3 - 7_10_3-check: | cd example.org cabal check @@ -192,7 +198,7 @@ tasks: cabal haddock all - 8_0_1-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.0.1 + cabal configure -w ghc-8.0.1 - 8_0_1-check: | cd example.org cabal check @@ -211,7 +217,7 @@ tasks: cabal haddock all - 8_0_2-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.0.2 + cabal configure -w ghc-8.0.2 - 8_0_2-check: | cd example.org cabal check @@ -230,7 +236,7 @@ tasks: cabal haddock all - 8_2_1-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.2.1 + cabal configure -w ghc-8.2.1 - 8_2_1-check: | cd example.org cabal check @@ -249,7 +255,7 @@ tasks: cabal haddock all - 8_2_2-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.2.2 + cabal configure -w ghc-8.2.2 - 8_2_2-check: | cd example.org cabal check @@ -268,7 +274,7 @@ tasks: cabal haddock all - 8_4_1-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.4.1 + cabal configure -w ghc-8.4.1 - 8_4_1-check: | cd example.org cabal check @@ -287,7 +293,7 @@ tasks: cabal haddock all - 8_4_2-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.4.2 + cabal configure -w ghc-8.4.2 - 8_4_2-check: | cd example.org cabal check @@ -306,7 +312,7 @@ tasks: cabal haddock all - 8_4_3-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.4.3 + cabal configure -w ghc-8.4.3 - 8_4_3-check: | cd example.org cabal check @@ -325,7 +331,7 @@ tasks: cabal haddock all - 8_4_4-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.4.4 + cabal configure -w ghc-8.4.4 - 8_4_4-check: | cd example.org cabal check @@ -344,7 +350,7 @@ tasks: cabal haddock all - 8_6_1-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.6.1 + cabal configure -w ghc-8.6.1 - 8_6_1-check: | cd example.org cabal check @@ -363,7 +369,7 @@ tasks: cabal haddock all - 8_6_2-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.6.2 + cabal configure -w ghc-8.6.2 - 8_6_2-check: | cd example.org cabal check @@ -382,7 +388,7 @@ tasks: cabal haddock all - 8_6_3-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.6.3 + cabal configure -w ghc-8.6.3 - 8_6_3-check: | cd example.org cabal check @@ -401,7 +407,7 @@ tasks: cabal haddock all - 8_6_4-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.6.4 + cabal configure -w ghc-8.6.4 - 8_6_4-check: | cd example.org cabal check @@ -420,7 +426,7 @@ tasks: cabal haddock all - 8_6_5-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.6.5 + cabal configure -w ghc-8.6.5 - 8_6_5-check: | cd example.org cabal check @@ -439,7 +445,7 @@ tasks: cabal haddock all - 8_8_1-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.8.1 + cabal configure -w ghc-8.8.1 - 8_8_1-check: | cd example.org cabal check @@ -458,7 +464,7 @@ tasks: cabal haddock all - 8_8_2-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.8.2 + cabal configure -w ghc-8.8.2 - 8_8_2-check: | cd example.org cabal check @@ -477,7 +483,7 @@ tasks: cabal haddock all - 8_8_3-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.8.3 + cabal configure -w ghc-8.8.3 - 8_8_3-check: | cd example.org cabal check @@ -496,7 +502,7 @@ tasks: cabal haddock all - 8_8_4-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.8.4 + cabal configure -w ghc-8.8.4 - 8_8_4-check: | cd example.org cabal check @@ -515,7 +521,7 @@ tasks: cabal haddock all - 8_10_1-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.1 + cabal configure -w ghc-8.10.1 - 8_10_1-check: | cd example.org cabal check @@ -534,7 +540,7 @@ tasks: cabal haddock all - 8_10_2-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.2 + cabal configure -w ghc-8.10.2 - 8_10_2-check: | cd example.org cabal check @@ -553,7 +559,7 @@ tasks: cabal haddock all - 8_10_3-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.3 + cabal configure -w ghc-8.10.3 - 8_10_3-check: | cd example.org cabal check @@ -572,7 +578,7 @@ tasks: cabal haddock all - 8_10_4-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.4 + cabal configure -w ghc-8.10.4 - 8_10_4-check: | cd example.org cabal check @@ -591,7 +597,7 @@ tasks: cabal haddock all - 8_10_5-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.5 + cabal configure -w ghc-8.10.5 - 8_10_5-check: | cd example.org cabal check @@ -610,7 +616,7 @@ tasks: cabal haddock all - 8_10_6-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.6 + cabal configure -w ghc-8.10.6 - 8_10_6-check: | cd example.org cabal check @@ -629,7 +635,7 @@ tasks: cabal haddock all - 8_10_7-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.7 + cabal configure -w ghc-8.10.7 - 8_10_7-check: | cd example.org cabal check diff --git a/fixtures/copy-fields-some.sourcehut b/fixtures/copy-fields-some.sourcehut index af721bc6..454b2526 100644 --- a/fixtures/copy-fields-some.sourcehut +++ b/fixtures/copy-fields-some.sourcehut @@ -16,7 +16,7 @@ image: ubuntu/bionic packages: - gcc - - cabal-install-3.4 + - libgmp-dev - ghc-7.8.1 - ghc-7.8.2 - ghc-7.8.3 @@ -45,21 +45,27 @@ packages: - ghc-8.10.2 - ghc-8.10.3 - ghc-8.10.4 - - ghc-8.10.5 - - ghc-8.10.6 - - ghc-8.10.7 repositories: hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 sources: - https://example.org tasks: - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + mkdir -p "$HOME/.ghcup/bin" + curl -sL https://downloads.haskell.org/ghcup/0.1.17.8/x86_64-linux-ghcup-0.1.17.8 > "$HOME/.ghcup/bin/ghcup" + chmod a+x "$HOME/.ghcup/bin/ghcup" + export PATH=$PATH:$HOME/.ghcup/bin + echo "export PATH=$PATH:$HOME/.ghcup/bin" >> ~/.buildenv + "$HOME/.ghcup/bin/ghcup" install cabal 3.6 + "$HOME/.ghcup/bin/ghcup" install ghc "ghc-8.10.5" + "$HOME/.ghcup/bin/ghcup" install ghc "ghc-8.10.6" + "$HOME/.ghcup/bin/ghcup" install ghc "ghc-8.10.7" + export PATH=$PATH:/opt/ghc/bin + echo "export PATH=$PATH:/opt/ghc/bin" >> ~/.buildenv cabal update - 7_8_1-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.8.1 + cabal configure -w ghc-7.8.1 - 7_8_1-check: | cd example.org cabal check @@ -78,7 +84,7 @@ tasks: cabal haddock all - 7_8_2-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.8.2 + cabal configure -w ghc-7.8.2 - 7_8_2-check: | cd example.org cabal check @@ -97,7 +103,7 @@ tasks: cabal haddock all - 7_8_3-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.8.3 + cabal configure -w ghc-7.8.3 - 7_8_3-check: | cd example.org cabal check @@ -116,7 +122,7 @@ tasks: cabal haddock all - 7_8_4-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.8.4 + cabal configure -w ghc-7.8.4 - 7_8_4-check: | cd example.org cabal check @@ -135,7 +141,7 @@ tasks: cabal haddock all - 7_10_1-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.10.1 + cabal configure -w ghc-7.10.1 - 7_10_1-check: | cd example.org cabal check @@ -154,7 +160,7 @@ tasks: cabal haddock all - 7_10_2-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.10.2 + cabal configure -w ghc-7.10.2 - 7_10_2-check: | cd example.org cabal check @@ -173,7 +179,7 @@ tasks: cabal haddock all - 7_10_3-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.10.3 + cabal configure -w ghc-7.10.3 - 7_10_3-check: | cd example.org cabal check @@ -192,7 +198,7 @@ tasks: cabal haddock all - 8_0_1-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.0.1 + cabal configure -w ghc-8.0.1 - 8_0_1-check: | cd example.org cabal check @@ -211,7 +217,7 @@ tasks: cabal haddock all - 8_0_2-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.0.2 + cabal configure -w ghc-8.0.2 - 8_0_2-check: | cd example.org cabal check @@ -230,7 +236,7 @@ tasks: cabal haddock all - 8_2_1-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.2.1 + cabal configure -w ghc-8.2.1 - 8_2_1-check: | cd example.org cabal check @@ -249,7 +255,7 @@ tasks: cabal haddock all - 8_2_2-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.2.2 + cabal configure -w ghc-8.2.2 - 8_2_2-check: | cd example.org cabal check @@ -268,7 +274,7 @@ tasks: cabal haddock all - 8_4_1-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.4.1 + cabal configure -w ghc-8.4.1 - 8_4_1-check: | cd example.org cabal check @@ -287,7 +293,7 @@ tasks: cabal haddock all - 8_4_2-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.4.2 + cabal configure -w ghc-8.4.2 - 8_4_2-check: | cd example.org cabal check @@ -306,7 +312,7 @@ tasks: cabal haddock all - 8_4_3-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.4.3 + cabal configure -w ghc-8.4.3 - 8_4_3-check: | cd example.org cabal check @@ -325,7 +331,7 @@ tasks: cabal haddock all - 8_4_4-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.4.4 + cabal configure -w ghc-8.4.4 - 8_4_4-check: | cd example.org cabal check @@ -344,7 +350,7 @@ tasks: cabal haddock all - 8_6_1-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.6.1 + cabal configure -w ghc-8.6.1 - 8_6_1-check: | cd example.org cabal check @@ -363,7 +369,7 @@ tasks: cabal haddock all - 8_6_2-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.6.2 + cabal configure -w ghc-8.6.2 - 8_6_2-check: | cd example.org cabal check @@ -382,7 +388,7 @@ tasks: cabal haddock all - 8_6_3-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.6.3 + cabal configure -w ghc-8.6.3 - 8_6_3-check: | cd example.org cabal check @@ -401,7 +407,7 @@ tasks: cabal haddock all - 8_6_4-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.6.4 + cabal configure -w ghc-8.6.4 - 8_6_4-check: | cd example.org cabal check @@ -420,7 +426,7 @@ tasks: cabal haddock all - 8_6_5-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.6.5 + cabal configure -w ghc-8.6.5 - 8_6_5-check: | cd example.org cabal check @@ -439,7 +445,7 @@ tasks: cabal haddock all - 8_8_1-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.8.1 + cabal configure -w ghc-8.8.1 - 8_8_1-check: | cd example.org cabal check @@ -458,7 +464,7 @@ tasks: cabal haddock all - 8_8_2-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.8.2 + cabal configure -w ghc-8.8.2 - 8_8_2-check: | cd example.org cabal check @@ -477,7 +483,7 @@ tasks: cabal haddock all - 8_8_3-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.8.3 + cabal configure -w ghc-8.8.3 - 8_8_3-check: | cd example.org cabal check @@ -496,7 +502,7 @@ tasks: cabal haddock all - 8_8_4-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.8.4 + cabal configure -w ghc-8.8.4 - 8_8_4-check: | cd example.org cabal check @@ -515,7 +521,7 @@ tasks: cabal haddock all - 8_10_1-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.1 + cabal configure -w ghc-8.10.1 - 8_10_1-check: | cd example.org cabal check @@ -534,7 +540,7 @@ tasks: cabal haddock all - 8_10_2-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.2 + cabal configure -w ghc-8.10.2 - 8_10_2-check: | cd example.org cabal check @@ -553,7 +559,7 @@ tasks: cabal haddock all - 8_10_3-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.3 + cabal configure -w ghc-8.10.3 - 8_10_3-check: | cd example.org cabal check @@ -572,7 +578,7 @@ tasks: cabal haddock all - 8_10_4-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.4 + cabal configure -w ghc-8.10.4 - 8_10_4-check: | cd example.org cabal check @@ -591,7 +597,7 @@ tasks: cabal haddock all - 8_10_5-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.5 + cabal configure -w ghc-8.10.5 - 8_10_5-check: | cd example.org cabal check @@ -610,7 +616,7 @@ tasks: cabal haddock all - 8_10_6-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.6 + cabal configure -w ghc-8.10.6 - 8_10_6-check: | cd example.org cabal check @@ -629,7 +635,7 @@ tasks: cabal haddock all - 8_10_7-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.7 + cabal configure -w ghc-8.10.7 - 8_10_7-check: | cd example.org cabal check diff --git a/fixtures/empty-line.sourcehut b/fixtures/empty-line.sourcehut index 463f6b1e..aa3c60d6 100644 --- a/fixtures/empty-line.sourcehut +++ b/fixtures/empty-line.sourcehut @@ -16,8 +16,7 @@ image: ubuntu/bionic packages: - gcc - - cabal-install-3.4 - - ghc-head + - libgmp-dev - ghc-7.8.1 - ghc-7.8.2 - ghc-7.8.3 @@ -46,21 +45,28 @@ packages: - ghc-8.10.2 - ghc-8.10.3 - ghc-8.10.4 - - ghc-8.10.5 - - ghc-8.10.6 - - ghc-8.10.7 repositories: hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 sources: - https://example.org tasks: - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + mkdir -p "$HOME/.ghcup/bin" + curl -sL https://downloads.haskell.org/ghcup/0.1.17.8/x86_64-linux-ghcup-0.1.17.8 > "$HOME/.ghcup/bin/ghcup" + chmod a+x "$HOME/.ghcup/bin/ghcup" + export PATH=$PATH:$HOME/.ghcup/bin + echo "export PATH=$PATH:$HOME/.ghcup/bin" >> ~/.buildenv + "$HOME/.ghcup/bin/ghcup" install cabal 3.6 + "$HOME/.ghcup/bin/ghcup" install ghc "ghc-head" + "$HOME/.ghcup/bin/ghcup" install ghc "ghc-8.10.5" + "$HOME/.ghcup/bin/ghcup" install ghc "ghc-8.10.6" + "$HOME/.ghcup/bin/ghcup" install ghc "ghc-8.10.7" + export PATH=$PATH:/opt/ghc/bin + echo "export PATH=$PATH:/opt/ghc/bin" >> ~/.buildenv cabal update - ghc-head-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-head + cabal configure -w ghc-head - ghc-head-check: | cd example.org cabal check @@ -79,7 +85,7 @@ tasks: cabal haddock all - 7_8_1-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.8.1 + cabal configure -w ghc-7.8.1 - 7_8_1-check: | cd example.org cabal check @@ -98,7 +104,7 @@ tasks: cabal haddock all - 7_8_2-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.8.2 + cabal configure -w ghc-7.8.2 - 7_8_2-check: | cd example.org cabal check @@ -117,7 +123,7 @@ tasks: cabal haddock all - 7_8_3-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.8.3 + cabal configure -w ghc-7.8.3 - 7_8_3-check: | cd example.org cabal check @@ -136,7 +142,7 @@ tasks: cabal haddock all - 7_8_4-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.8.4 + cabal configure -w ghc-7.8.4 - 7_8_4-check: | cd example.org cabal check @@ -155,7 +161,7 @@ tasks: cabal haddock all - 7_10_1-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.10.1 + cabal configure -w ghc-7.10.1 - 7_10_1-check: | cd example.org cabal check @@ -174,7 +180,7 @@ tasks: cabal haddock all - 7_10_2-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.10.2 + cabal configure -w ghc-7.10.2 - 7_10_2-check: | cd example.org cabal check @@ -193,7 +199,7 @@ tasks: cabal haddock all - 7_10_3-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.10.3 + cabal configure -w ghc-7.10.3 - 7_10_3-check: | cd example.org cabal check @@ -212,7 +218,7 @@ tasks: cabal haddock all - 8_0_1-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.0.1 + cabal configure -w ghc-8.0.1 - 8_0_1-check: | cd example.org cabal check @@ -231,7 +237,7 @@ tasks: cabal haddock all - 8_0_2-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.0.2 + cabal configure -w ghc-8.0.2 - 8_0_2-check: | cd example.org cabal check @@ -250,7 +256,7 @@ tasks: cabal haddock all - 8_2_1-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.2.1 + cabal configure -w ghc-8.2.1 - 8_2_1-check: | cd example.org cabal check @@ -269,7 +275,7 @@ tasks: cabal haddock all - 8_2_2-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.2.2 + cabal configure -w ghc-8.2.2 - 8_2_2-check: | cd example.org cabal check @@ -288,7 +294,7 @@ tasks: cabal haddock all - 8_4_1-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.4.1 + cabal configure -w ghc-8.4.1 - 8_4_1-check: | cd example.org cabal check @@ -307,7 +313,7 @@ tasks: cabal haddock all - 8_4_2-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.4.2 + cabal configure -w ghc-8.4.2 - 8_4_2-check: | cd example.org cabal check @@ -326,7 +332,7 @@ tasks: cabal haddock all - 8_4_3-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.4.3 + cabal configure -w ghc-8.4.3 - 8_4_3-check: | cd example.org cabal check @@ -345,7 +351,7 @@ tasks: cabal haddock all - 8_4_4-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.4.4 + cabal configure -w ghc-8.4.4 - 8_4_4-check: | cd example.org cabal check @@ -364,7 +370,7 @@ tasks: cabal haddock all - 8_6_1-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.6.1 + cabal configure -w ghc-8.6.1 - 8_6_1-check: | cd example.org cabal check @@ -383,7 +389,7 @@ tasks: cabal haddock all - 8_6_2-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.6.2 + cabal configure -w ghc-8.6.2 - 8_6_2-check: | cd example.org cabal check @@ -402,7 +408,7 @@ tasks: cabal haddock all - 8_6_3-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.6.3 + cabal configure -w ghc-8.6.3 - 8_6_3-check: | cd example.org cabal check @@ -421,7 +427,7 @@ tasks: cabal haddock all - 8_6_4-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.6.4 + cabal configure -w ghc-8.6.4 - 8_6_4-check: | cd example.org cabal check @@ -440,7 +446,7 @@ tasks: cabal haddock all - 8_6_5-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.6.5 + cabal configure -w ghc-8.6.5 - 8_6_5-check: | cd example.org cabal check @@ -459,7 +465,7 @@ tasks: cabal haddock all - 8_8_1-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.8.1 + cabal configure -w ghc-8.8.1 - 8_8_1-check: | cd example.org cabal check @@ -478,7 +484,7 @@ tasks: cabal haddock all - 8_8_2-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.8.2 + cabal configure -w ghc-8.8.2 - 8_8_2-check: | cd example.org cabal check @@ -497,7 +503,7 @@ tasks: cabal haddock all - 8_8_3-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.8.3 + cabal configure -w ghc-8.8.3 - 8_8_3-check: | cd example.org cabal check @@ -516,7 +522,7 @@ tasks: cabal haddock all - 8_8_4-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.8.4 + cabal configure -w ghc-8.8.4 - 8_8_4-check: | cd example.org cabal check @@ -535,7 +541,7 @@ tasks: cabal haddock all - 8_10_1-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.1 + cabal configure -w ghc-8.10.1 - 8_10_1-check: | cd example.org cabal check @@ -554,7 +560,7 @@ tasks: cabal haddock all - 8_10_2-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.2 + cabal configure -w ghc-8.10.2 - 8_10_2-check: | cd example.org cabal check @@ -573,7 +579,7 @@ tasks: cabal haddock all - 8_10_3-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.3 + cabal configure -w ghc-8.10.3 - 8_10_3-check: | cd example.org cabal check @@ -592,7 +598,7 @@ tasks: cabal haddock all - 8_10_4-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.4 + cabal configure -w ghc-8.10.4 - 8_10_4-check: | cd example.org cabal check @@ -611,7 +617,7 @@ tasks: cabal haddock all - 8_10_5-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.5 + cabal configure -w ghc-8.10.5 - 8_10_5-check: | cd example.org cabal check @@ -630,7 +636,7 @@ tasks: cabal haddock all - 8_10_6-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.6 + cabal configure -w ghc-8.10.6 - 8_10_6-check: | cd example.org cabal check @@ -649,7 +655,7 @@ tasks: cabal haddock all - 8_10_7-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.7 + cabal configure -w ghc-8.10.7 - 8_10_7-check: | cd example.org cabal check diff --git a/fixtures/enabled-jobs.sourcehut b/fixtures/enabled-jobs.sourcehut index 851862bb..e208a267 100644 --- a/fixtures/enabled-jobs.sourcehut +++ b/fixtures/enabled-jobs.sourcehut @@ -16,7 +16,7 @@ image: ubuntu/bionic packages: - gcc - - cabal-install-3.4 + - libgmp-dev - ghc-8.0.1 - ghc-8.0.2 - ghc-8.2.1 @@ -38,15 +38,7 @@ packages: - ghc-8.10.2 - ghc-8.10.3 - ghc-8.10.4 - - ghc-8.10.5 - - ghc-8.10.6 - - ghc-8.10.7 - ghc-9.0.1 - - ghc-9.0.2 - - ghc-9.2.1 - - ghc-9.2.2 - - ghc-9.2.3 - - ghc-9.4.1 - ghcjs-8.4 repositories: hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 @@ -54,12 +46,26 @@ sources: - https://example.org tasks: - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + mkdir -p "$HOME/.ghcup/bin" + curl -sL https://downloads.haskell.org/ghcup/0.1.17.8/x86_64-linux-ghcup-0.1.17.8 > "$HOME/.ghcup/bin/ghcup" + chmod a+x "$HOME/.ghcup/bin/ghcup" + export PATH=$PATH:$HOME/.ghcup/bin + echo "export PATH=$PATH:$HOME/.ghcup/bin" >> ~/.buildenv + "$HOME/.ghcup/bin/ghcup" install cabal 3.6 + "$HOME/.ghcup/bin/ghcup" install ghc "ghc-8.10.5" + "$HOME/.ghcup/bin/ghcup" install ghc "ghc-8.10.6" + "$HOME/.ghcup/bin/ghcup" install ghc "ghc-8.10.7" + "$HOME/.ghcup/bin/ghcup" install ghc "ghc-9.0.2" + "$HOME/.ghcup/bin/ghcup" install ghc "ghc-9.2.1" + "$HOME/.ghcup/bin/ghcup" install ghc "ghc-9.2.2" + "$HOME/.ghcup/bin/ghcup" install ghc "ghc-9.2.3" + "$HOME/.ghcup/bin/ghcup" install ghc "ghc-9.4.1" + export PATH=$PATH:/opt/ghc/bin + echo "export PATH=$PATH:/opt/ghc/bin" >> ~/.buildenv cabal update - 8_0_1-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.0.1 + cabal configure -w ghc-8.0.1 - 8_0_1-check: | cd example.org cabal check @@ -78,7 +84,7 @@ tasks: cabal haddock all - 8_0_2-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.0.2 + cabal configure -w ghc-8.0.2 - 8_0_2-check: | cd example.org cabal check @@ -97,7 +103,7 @@ tasks: cabal haddock all - 8_2_1-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.2.1 + cabal configure -w ghc-8.2.1 - 8_2_1-check: | cd example.org cabal check @@ -116,7 +122,7 @@ tasks: cabal haddock all - 8_2_2-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.2.2 + cabal configure -w ghc-8.2.2 - 8_2_2-check: | cd example.org cabal check @@ -135,7 +141,7 @@ tasks: cabal haddock all - 8_4_1-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.4.1 + cabal configure -w ghc-8.4.1 - 8_4_1-check: | cd example.org cabal check @@ -154,7 +160,7 @@ tasks: cabal haddock all - 8_4_2-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.4.2 + cabal configure -w ghc-8.4.2 - 8_4_2-check: | cd example.org cabal check @@ -173,7 +179,7 @@ tasks: cabal haddock all - 8_4_3-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.4.3 + cabal configure -w ghc-8.4.3 - 8_4_3-check: | cd example.org cabal check @@ -192,7 +198,7 @@ tasks: cabal haddock all - 8_4_4-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.4.4 + cabal configure -w ghc-8.4.4 - 8_4_4-check: | cd example.org cabal check @@ -211,7 +217,7 @@ tasks: cabal haddock all - 8_6_1-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.6.1 + cabal configure -w ghc-8.6.1 - 8_6_1-check: | cd example.org cabal check @@ -230,7 +236,7 @@ tasks: cabal haddock all - 8_6_2-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.6.2 + cabal configure -w ghc-8.6.2 - 8_6_2-check: | cd example.org cabal check @@ -249,7 +255,7 @@ tasks: cabal haddock all - 8_6_3-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.6.3 + cabal configure -w ghc-8.6.3 - 8_6_3-check: | cd example.org cabal check @@ -268,7 +274,7 @@ tasks: cabal haddock all - 8_6_4-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.6.4 + cabal configure -w ghc-8.6.4 - 8_6_4-check: | cd example.org cabal check @@ -287,7 +293,7 @@ tasks: cabal haddock all - 8_6_5-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.6.5 + cabal configure -w ghc-8.6.5 - 8_6_5-check: | cd example.org cabal check @@ -306,7 +312,7 @@ tasks: cabal haddock all - 8_8_1-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.8.1 + cabal configure -w ghc-8.8.1 - 8_8_1-check: | cd example.org cabal check @@ -325,7 +331,7 @@ tasks: cabal haddock all - 8_8_2-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.8.2 + cabal configure -w ghc-8.8.2 - 8_8_2-check: | cd example.org cabal check @@ -344,7 +350,7 @@ tasks: cabal haddock all - 8_8_3-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.8.3 + cabal configure -w ghc-8.8.3 - 8_8_3-check: | cd example.org cabal check @@ -363,7 +369,7 @@ tasks: cabal haddock all - 8_8_4-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.8.4 + cabal configure -w ghc-8.8.4 - 8_8_4-check: | cd example.org cabal check @@ -382,7 +388,7 @@ tasks: cabal haddock all - 8_10_1-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.1 + cabal configure -w ghc-8.10.1 - 8_10_1-check: | cd example.org cabal check @@ -401,7 +407,7 @@ tasks: cabal haddock all - 8_10_2-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.2 + cabal configure -w ghc-8.10.2 - 8_10_2-check: | cd example.org cabal check @@ -420,7 +426,7 @@ tasks: cabal haddock all - 8_10_3-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.3 + cabal configure -w ghc-8.10.3 - 8_10_3-check: | cd example.org cabal check @@ -439,7 +445,7 @@ tasks: cabal haddock all - 8_10_4-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.4 + cabal configure -w ghc-8.10.4 - 8_10_4-check: | cd example.org cabal check @@ -458,7 +464,7 @@ tasks: cabal haddock all - 8_10_5-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.5 + cabal configure -w ghc-8.10.5 - 8_10_5-check: | cd example.org cabal check @@ -477,7 +483,7 @@ tasks: cabal haddock all - 8_10_6-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.6 + cabal configure -w ghc-8.10.6 - 8_10_6-check: | cd example.org cabal check @@ -496,7 +502,7 @@ tasks: cabal haddock all - 8_10_7-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.7 + cabal configure -w ghc-8.10.7 - 8_10_7-check: | cd example.org cabal check @@ -515,7 +521,7 @@ tasks: cabal haddock all - 9_0_1-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-9.0.1 + cabal configure -w ghc-9.0.1 - 9_0_1-check: | cd example.org cabal check @@ -534,7 +540,7 @@ tasks: cabal haddock all - 9_0_2-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-9.0.2 + cabal configure -w ghc-9.0.2 - 9_0_2-check: | cd example.org cabal check @@ -553,7 +559,7 @@ tasks: cabal haddock all - 9_2_1-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-9.2.1 + cabal configure -w ghc-9.2.1 - 9_2_1-check: | cd example.org cabal check @@ -572,7 +578,7 @@ tasks: cabal haddock all - 9_2_2-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-9.2.2 + cabal configure -w ghc-9.2.2 - 9_2_2-check: | cd example.org cabal check @@ -591,7 +597,7 @@ tasks: cabal haddock all - 9_2_3-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-9.2.3 + cabal configure -w ghc-9.2.3 - 9_2_3-check: | cd example.org cabal check @@ -610,7 +616,7 @@ tasks: cabal haddock all - 9_4_1-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-9.4.1 + cabal configure -w ghc-9.4.1 - 9_4_1-check: | cd example.org cabal check @@ -629,7 +635,7 @@ tasks: cabal haddock all - ghcjs-8_4-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghcjs-8.4 + cabal configure -w ghcjs-8.4 - ghcjs-8_4-check: | cd example.org cabal check diff --git a/fixtures/irc-channels.sourcehut b/fixtures/irc-channels.sourcehut index 8ab83ba1..55895879 100644 --- a/fixtures/irc-channels.sourcehut +++ b/fixtures/irc-channels.sourcehut @@ -16,7 +16,7 @@ image: ubuntu/bionic packages: - gcc - - cabal-install-3.4 + - libgmp-dev - ghc-7.8.1 - ghc-7.8.2 - ghc-7.8.3 @@ -45,21 +45,27 @@ packages: - ghc-8.10.2 - ghc-8.10.3 - ghc-8.10.4 - - ghc-8.10.5 - - ghc-8.10.6 - - ghc-8.10.7 repositories: hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 sources: - https://example.org tasks: - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + mkdir -p "$HOME/.ghcup/bin" + curl -sL https://downloads.haskell.org/ghcup/0.1.17.8/x86_64-linux-ghcup-0.1.17.8 > "$HOME/.ghcup/bin/ghcup" + chmod a+x "$HOME/.ghcup/bin/ghcup" + export PATH=$PATH:$HOME/.ghcup/bin + echo "export PATH=$PATH:$HOME/.ghcup/bin" >> ~/.buildenv + "$HOME/.ghcup/bin/ghcup" install cabal 3.6 + "$HOME/.ghcup/bin/ghcup" install ghc "ghc-8.10.5" + "$HOME/.ghcup/bin/ghcup" install ghc "ghc-8.10.6" + "$HOME/.ghcup/bin/ghcup" install ghc "ghc-8.10.7" + export PATH=$PATH:/opt/ghc/bin + echo "export PATH=$PATH:/opt/ghc/bin" >> ~/.buildenv cabal update - 7_8_1-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.8.1 + cabal configure -w ghc-7.8.1 - 7_8_1-check: | cd example.org cabal check @@ -78,7 +84,7 @@ tasks: cabal haddock all - 7_8_2-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.8.2 + cabal configure -w ghc-7.8.2 - 7_8_2-check: | cd example.org cabal check @@ -97,7 +103,7 @@ tasks: cabal haddock all - 7_8_3-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.8.3 + cabal configure -w ghc-7.8.3 - 7_8_3-check: | cd example.org cabal check @@ -116,7 +122,7 @@ tasks: cabal haddock all - 7_8_4-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.8.4 + cabal configure -w ghc-7.8.4 - 7_8_4-check: | cd example.org cabal check @@ -135,7 +141,7 @@ tasks: cabal haddock all - 7_10_1-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.10.1 + cabal configure -w ghc-7.10.1 - 7_10_1-check: | cd example.org cabal check @@ -154,7 +160,7 @@ tasks: cabal haddock all - 7_10_2-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.10.2 + cabal configure -w ghc-7.10.2 - 7_10_2-check: | cd example.org cabal check @@ -173,7 +179,7 @@ tasks: cabal haddock all - 7_10_3-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.10.3 + cabal configure -w ghc-7.10.3 - 7_10_3-check: | cd example.org cabal check @@ -192,7 +198,7 @@ tasks: cabal haddock all - 8_0_1-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.0.1 + cabal configure -w ghc-8.0.1 - 8_0_1-check: | cd example.org cabal check @@ -211,7 +217,7 @@ tasks: cabal haddock all - 8_0_2-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.0.2 + cabal configure -w ghc-8.0.2 - 8_0_2-check: | cd example.org cabal check @@ -230,7 +236,7 @@ tasks: cabal haddock all - 8_2_1-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.2.1 + cabal configure -w ghc-8.2.1 - 8_2_1-check: | cd example.org cabal check @@ -249,7 +255,7 @@ tasks: cabal haddock all - 8_2_2-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.2.2 + cabal configure -w ghc-8.2.2 - 8_2_2-check: | cd example.org cabal check @@ -268,7 +274,7 @@ tasks: cabal haddock all - 8_4_1-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.4.1 + cabal configure -w ghc-8.4.1 - 8_4_1-check: | cd example.org cabal check @@ -287,7 +293,7 @@ tasks: cabal haddock all - 8_4_2-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.4.2 + cabal configure -w ghc-8.4.2 - 8_4_2-check: | cd example.org cabal check @@ -306,7 +312,7 @@ tasks: cabal haddock all - 8_4_3-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.4.3 + cabal configure -w ghc-8.4.3 - 8_4_3-check: | cd example.org cabal check @@ -325,7 +331,7 @@ tasks: cabal haddock all - 8_4_4-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.4.4 + cabal configure -w ghc-8.4.4 - 8_4_4-check: | cd example.org cabal check @@ -344,7 +350,7 @@ tasks: cabal haddock all - 8_6_1-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.6.1 + cabal configure -w ghc-8.6.1 - 8_6_1-check: | cd example.org cabal check @@ -363,7 +369,7 @@ tasks: cabal haddock all - 8_6_2-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.6.2 + cabal configure -w ghc-8.6.2 - 8_6_2-check: | cd example.org cabal check @@ -382,7 +388,7 @@ tasks: cabal haddock all - 8_6_3-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.6.3 + cabal configure -w ghc-8.6.3 - 8_6_3-check: | cd example.org cabal check @@ -401,7 +407,7 @@ tasks: cabal haddock all - 8_6_4-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.6.4 + cabal configure -w ghc-8.6.4 - 8_6_4-check: | cd example.org cabal check @@ -420,7 +426,7 @@ tasks: cabal haddock all - 8_6_5-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.6.5 + cabal configure -w ghc-8.6.5 - 8_6_5-check: | cd example.org cabal check @@ -439,7 +445,7 @@ tasks: cabal haddock all - 8_8_1-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.8.1 + cabal configure -w ghc-8.8.1 - 8_8_1-check: | cd example.org cabal check @@ -458,7 +464,7 @@ tasks: cabal haddock all - 8_8_2-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.8.2 + cabal configure -w ghc-8.8.2 - 8_8_2-check: | cd example.org cabal check @@ -477,7 +483,7 @@ tasks: cabal haddock all - 8_8_3-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.8.3 + cabal configure -w ghc-8.8.3 - 8_8_3-check: | cd example.org cabal check @@ -496,7 +502,7 @@ tasks: cabal haddock all - 8_8_4-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.8.4 + cabal configure -w ghc-8.8.4 - 8_8_4-check: | cd example.org cabal check @@ -515,7 +521,7 @@ tasks: cabal haddock all - 8_10_1-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.1 + cabal configure -w ghc-8.10.1 - 8_10_1-check: | cd example.org cabal check @@ -534,7 +540,7 @@ tasks: cabal haddock all - 8_10_2-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.2 + cabal configure -w ghc-8.10.2 - 8_10_2-check: | cd example.org cabal check @@ -553,7 +559,7 @@ tasks: cabal haddock all - 8_10_3-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.3 + cabal configure -w ghc-8.10.3 - 8_10_3-check: | cd example.org cabal check @@ -572,7 +578,7 @@ tasks: cabal haddock all - 8_10_4-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.4 + cabal configure -w ghc-8.10.4 - 8_10_4-check: | cd example.org cabal check @@ -591,7 +597,7 @@ tasks: cabal haddock all - 8_10_5-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.5 + cabal configure -w ghc-8.10.5 - 8_10_5-check: | cd example.org cabal check @@ -610,7 +616,7 @@ tasks: cabal haddock all - 8_10_6-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.6 + cabal configure -w ghc-8.10.6 - 8_10_6-check: | cd example.org cabal check @@ -629,7 +635,7 @@ tasks: cabal haddock all - 8_10_7-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.7 + cabal configure -w ghc-8.10.7 - 8_10_7-check: | cd example.org cabal check diff --git a/fixtures/messy.sourcehut b/fixtures/messy.sourcehut index e4359340..bb6fd695 100644 --- a/fixtures/messy.sourcehut +++ b/fixtures/messy.sourcehut @@ -15,10 +15,9 @@ # image: ubuntu/bionic packages: - - fftw3-dev - gcc - - cabal-install-3.4 - - ghc-head + - libgmp-dev + - fftw3-dev - ghc-7.8.1 - ghc-7.8.2 - ghc-7.8.3 @@ -47,21 +46,28 @@ packages: - ghc-8.10.2 - ghc-8.10.3 - ghc-8.10.4 - - ghc-8.10.5 - - ghc-8.10.6 - - ghc-8.10.7 repositories: hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 sources: - https://example.org tasks: - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + mkdir -p "$HOME/.ghcup/bin" + curl -sL https://downloads.haskell.org/ghcup/0.1.17.8/x86_64-linux-ghcup-0.1.17.8 > "$HOME/.ghcup/bin/ghcup" + chmod a+x "$HOME/.ghcup/bin/ghcup" + export PATH=$PATH:$HOME/.ghcup/bin + echo "export PATH=$PATH:$HOME/.ghcup/bin" >> ~/.buildenv + "$HOME/.ghcup/bin/ghcup" install cabal 3.6 + "$HOME/.ghcup/bin/ghcup" install ghc "ghc-head" + "$HOME/.ghcup/bin/ghcup" install ghc "ghc-8.10.5" + "$HOME/.ghcup/bin/ghcup" install ghc "ghc-8.10.6" + "$HOME/.ghcup/bin/ghcup" install ghc "ghc-8.10.7" + export PATH=$PATH:/opt/ghc/bin + echo "export PATH=$PATH:/opt/ghc/bin" >> ~/.buildenv cabal update - ghc-head-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-head + cabal configure -w ghc-head - ghc-head-check: | cd example.org cabal check @@ -80,7 +86,7 @@ tasks: cabal haddock all - 7_8_1-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.8.1 + cabal configure -w ghc-7.8.1 - 7_8_1-check: | cd example.org cabal check @@ -99,7 +105,7 @@ tasks: cabal haddock all - 7_8_2-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.8.2 + cabal configure -w ghc-7.8.2 - 7_8_2-check: | cd example.org cabal check @@ -118,7 +124,7 @@ tasks: cabal haddock all - 7_8_3-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.8.3 + cabal configure -w ghc-7.8.3 - 7_8_3-check: | cd example.org cabal check @@ -137,7 +143,7 @@ tasks: cabal haddock all - 7_8_4-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.8.4 + cabal configure -w ghc-7.8.4 - 7_8_4-check: | cd example.org cabal check @@ -156,7 +162,7 @@ tasks: cabal haddock all - 7_10_1-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.10.1 + cabal configure -w ghc-7.10.1 - 7_10_1-check: | cd example.org cabal check @@ -175,7 +181,7 @@ tasks: cabal haddock all - 7_10_2-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.10.2 + cabal configure -w ghc-7.10.2 - 7_10_2-check: | cd example.org cabal check @@ -194,7 +200,7 @@ tasks: cabal haddock all - 7_10_3-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.10.3 + cabal configure -w ghc-7.10.3 - 7_10_3-check: | cd example.org cabal check @@ -213,7 +219,7 @@ tasks: cabal haddock all - 8_0_1-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.0.1 + cabal configure -w ghc-8.0.1 - 8_0_1-check: | cd example.org cabal check @@ -232,7 +238,7 @@ tasks: cabal haddock all - 8_0_2-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.0.2 + cabal configure -w ghc-8.0.2 - 8_0_2-check: | cd example.org cabal check @@ -251,7 +257,7 @@ tasks: cabal haddock all - 8_2_1-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.2.1 + cabal configure -w ghc-8.2.1 - 8_2_1-check: | cd example.org cabal check @@ -270,7 +276,7 @@ tasks: cabal haddock all - 8_2_2-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.2.2 + cabal configure -w ghc-8.2.2 - 8_2_2-check: | cd example.org cabal check @@ -289,7 +295,7 @@ tasks: cabal haddock all - 8_4_1-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.4.1 + cabal configure -w ghc-8.4.1 - 8_4_1-check: | cd example.org cabal check @@ -308,7 +314,7 @@ tasks: cabal haddock all - 8_4_2-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.4.2 + cabal configure -w ghc-8.4.2 - 8_4_2-check: | cd example.org cabal check @@ -327,7 +333,7 @@ tasks: cabal haddock all - 8_4_3-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.4.3 + cabal configure -w ghc-8.4.3 - 8_4_3-check: | cd example.org cabal check @@ -346,7 +352,7 @@ tasks: cabal haddock all - 8_4_4-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.4.4 + cabal configure -w ghc-8.4.4 - 8_4_4-check: | cd example.org cabal check @@ -365,7 +371,7 @@ tasks: cabal haddock all - 8_6_1-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.6.1 + cabal configure -w ghc-8.6.1 - 8_6_1-check: | cd example.org cabal check @@ -384,7 +390,7 @@ tasks: cabal haddock all - 8_6_2-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.6.2 + cabal configure -w ghc-8.6.2 - 8_6_2-check: | cd example.org cabal check @@ -403,7 +409,7 @@ tasks: cabal haddock all - 8_6_3-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.6.3 + cabal configure -w ghc-8.6.3 - 8_6_3-check: | cd example.org cabal check @@ -422,7 +428,7 @@ tasks: cabal haddock all - 8_6_4-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.6.4 + cabal configure -w ghc-8.6.4 - 8_6_4-check: | cd example.org cabal check @@ -441,7 +447,7 @@ tasks: cabal haddock all - 8_6_5-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.6.5 + cabal configure -w ghc-8.6.5 - 8_6_5-check: | cd example.org cabal check @@ -460,7 +466,7 @@ tasks: cabal haddock all - 8_8_1-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.8.1 + cabal configure -w ghc-8.8.1 - 8_8_1-check: | cd example.org cabal check @@ -479,7 +485,7 @@ tasks: cabal haddock all - 8_8_2-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.8.2 + cabal configure -w ghc-8.8.2 - 8_8_2-check: | cd example.org cabal check @@ -498,7 +504,7 @@ tasks: cabal haddock all - 8_8_3-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.8.3 + cabal configure -w ghc-8.8.3 - 8_8_3-check: | cd example.org cabal check @@ -517,7 +523,7 @@ tasks: cabal haddock all - 8_8_4-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.8.4 + cabal configure -w ghc-8.8.4 - 8_8_4-check: | cd example.org cabal check @@ -536,7 +542,7 @@ tasks: cabal haddock all - 8_10_1-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.1 + cabal configure -w ghc-8.10.1 - 8_10_1-check: | cd example.org cabal check @@ -555,7 +561,7 @@ tasks: cabal haddock all - 8_10_2-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.2 + cabal configure -w ghc-8.10.2 - 8_10_2-check: | cd example.org cabal check @@ -574,7 +580,7 @@ tasks: cabal haddock all - 8_10_3-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.3 + cabal configure -w ghc-8.10.3 - 8_10_3-check: | cd example.org cabal check @@ -593,7 +599,7 @@ tasks: cabal haddock all - 8_10_4-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.4 + cabal configure -w ghc-8.10.4 - 8_10_4-check: | cd example.org cabal check @@ -612,7 +618,7 @@ tasks: cabal haddock all - 8_10_5-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.5 + cabal configure -w ghc-8.10.5 - 8_10_5-check: | cd example.org cabal check @@ -631,7 +637,7 @@ tasks: cabal haddock all - 8_10_6-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.6 + cabal configure -w ghc-8.10.6 - 8_10_6-check: | cd example.org cabal check @@ -650,7 +656,7 @@ tasks: cabal haddock all - 8_10_7-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.7 + cabal configure -w ghc-8.10.7 - 8_10_7-check: | cd example.org cabal check diff --git a/fixtures/psql.sourcehut b/fixtures/psql.sourcehut index dd49bdef..57ab7924 100644 --- a/fixtures/psql.sourcehut +++ b/fixtures/psql.sourcehut @@ -16,7 +16,7 @@ image: ubuntu/bionic packages: - gcc - - cabal-install-3.4 + - libgmp-dev - ghc-7.8.1 - ghc-7.8.2 - ghc-7.8.3 @@ -45,21 +45,27 @@ packages: - ghc-8.10.2 - ghc-8.10.3 - ghc-8.10.4 - - ghc-8.10.5 - - ghc-8.10.6 - - ghc-8.10.7 repositories: hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 sources: - https://example.org tasks: - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + mkdir -p "$HOME/.ghcup/bin" + curl -sL https://downloads.haskell.org/ghcup/0.1.17.8/x86_64-linux-ghcup-0.1.17.8 > "$HOME/.ghcup/bin/ghcup" + chmod a+x "$HOME/.ghcup/bin/ghcup" + export PATH=$PATH:$HOME/.ghcup/bin + echo "export PATH=$PATH:$HOME/.ghcup/bin" >> ~/.buildenv + "$HOME/.ghcup/bin/ghcup" install cabal 3.6 + "$HOME/.ghcup/bin/ghcup" install ghc "ghc-8.10.5" + "$HOME/.ghcup/bin/ghcup" install ghc "ghc-8.10.6" + "$HOME/.ghcup/bin/ghcup" install ghc "ghc-8.10.7" + export PATH=$PATH:/opt/ghc/bin + echo "export PATH=$PATH:/opt/ghc/bin" >> ~/.buildenv cabal update - 7_8_1-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.8.1 + cabal configure -w ghc-7.8.1 - 7_8_1-check: | cd example.org cabal check @@ -78,7 +84,7 @@ tasks: cabal haddock all - 7_8_2-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.8.2 + cabal configure -w ghc-7.8.2 - 7_8_2-check: | cd example.org cabal check @@ -97,7 +103,7 @@ tasks: cabal haddock all - 7_8_3-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.8.3 + cabal configure -w ghc-7.8.3 - 7_8_3-check: | cd example.org cabal check @@ -116,7 +122,7 @@ tasks: cabal haddock all - 7_8_4-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.8.4 + cabal configure -w ghc-7.8.4 - 7_8_4-check: | cd example.org cabal check @@ -135,7 +141,7 @@ tasks: cabal haddock all - 7_10_1-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.10.1 + cabal configure -w ghc-7.10.1 - 7_10_1-check: | cd example.org cabal check @@ -154,7 +160,7 @@ tasks: cabal haddock all - 7_10_2-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.10.2 + cabal configure -w ghc-7.10.2 - 7_10_2-check: | cd example.org cabal check @@ -173,7 +179,7 @@ tasks: cabal haddock all - 7_10_3-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.10.3 + cabal configure -w ghc-7.10.3 - 7_10_3-check: | cd example.org cabal check @@ -192,7 +198,7 @@ tasks: cabal haddock all - 8_0_1-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.0.1 + cabal configure -w ghc-8.0.1 - 8_0_1-check: | cd example.org cabal check @@ -211,7 +217,7 @@ tasks: cabal haddock all - 8_0_2-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.0.2 + cabal configure -w ghc-8.0.2 - 8_0_2-check: | cd example.org cabal check @@ -230,7 +236,7 @@ tasks: cabal haddock all - 8_2_1-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.2.1 + cabal configure -w ghc-8.2.1 - 8_2_1-check: | cd example.org cabal check @@ -249,7 +255,7 @@ tasks: cabal haddock all - 8_2_2-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.2.2 + cabal configure -w ghc-8.2.2 - 8_2_2-check: | cd example.org cabal check @@ -268,7 +274,7 @@ tasks: cabal haddock all - 8_4_1-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.4.1 + cabal configure -w ghc-8.4.1 - 8_4_1-check: | cd example.org cabal check @@ -287,7 +293,7 @@ tasks: cabal haddock all - 8_4_2-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.4.2 + cabal configure -w ghc-8.4.2 - 8_4_2-check: | cd example.org cabal check @@ -306,7 +312,7 @@ tasks: cabal haddock all - 8_4_3-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.4.3 + cabal configure -w ghc-8.4.3 - 8_4_3-check: | cd example.org cabal check @@ -325,7 +331,7 @@ tasks: cabal haddock all - 8_4_4-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.4.4 + cabal configure -w ghc-8.4.4 - 8_4_4-check: | cd example.org cabal check @@ -344,7 +350,7 @@ tasks: cabal haddock all - 8_6_1-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.6.1 + cabal configure -w ghc-8.6.1 - 8_6_1-check: | cd example.org cabal check @@ -363,7 +369,7 @@ tasks: cabal haddock all - 8_6_2-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.6.2 + cabal configure -w ghc-8.6.2 - 8_6_2-check: | cd example.org cabal check @@ -382,7 +388,7 @@ tasks: cabal haddock all - 8_6_3-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.6.3 + cabal configure -w ghc-8.6.3 - 8_6_3-check: | cd example.org cabal check @@ -401,7 +407,7 @@ tasks: cabal haddock all - 8_6_4-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.6.4 + cabal configure -w ghc-8.6.4 - 8_6_4-check: | cd example.org cabal check @@ -420,7 +426,7 @@ tasks: cabal haddock all - 8_6_5-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.6.5 + cabal configure -w ghc-8.6.5 - 8_6_5-check: | cd example.org cabal check @@ -439,7 +445,7 @@ tasks: cabal haddock all - 8_8_1-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.8.1 + cabal configure -w ghc-8.8.1 - 8_8_1-check: | cd example.org cabal check @@ -458,7 +464,7 @@ tasks: cabal haddock all - 8_8_2-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.8.2 + cabal configure -w ghc-8.8.2 - 8_8_2-check: | cd example.org cabal check @@ -477,7 +483,7 @@ tasks: cabal haddock all - 8_8_3-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.8.3 + cabal configure -w ghc-8.8.3 - 8_8_3-check: | cd example.org cabal check @@ -496,7 +502,7 @@ tasks: cabal haddock all - 8_8_4-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.8.4 + cabal configure -w ghc-8.8.4 - 8_8_4-check: | cd example.org cabal check @@ -515,7 +521,7 @@ tasks: cabal haddock all - 8_10_1-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.1 + cabal configure -w ghc-8.10.1 - 8_10_1-check: | cd example.org cabal check @@ -534,7 +540,7 @@ tasks: cabal haddock all - 8_10_2-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.2 + cabal configure -w ghc-8.10.2 - 8_10_2-check: | cd example.org cabal check @@ -553,7 +559,7 @@ tasks: cabal haddock all - 8_10_3-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.3 + cabal configure -w ghc-8.10.3 - 8_10_3-check: | cd example.org cabal check @@ -572,7 +578,7 @@ tasks: cabal haddock all - 8_10_4-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.4 + cabal configure -w ghc-8.10.4 - 8_10_4-check: | cd example.org cabal check @@ -591,7 +597,7 @@ tasks: cabal haddock all - 8_10_5-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.5 + cabal configure -w ghc-8.10.5 - 8_10_5-check: | cd example.org cabal check @@ -610,7 +616,7 @@ tasks: cabal haddock all - 8_10_6-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.6 + cabal configure -w ghc-8.10.6 - 8_10_6-check: | cd example.org cabal check @@ -629,7 +635,7 @@ tasks: cabal haddock all - 8_10_7-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.7 + cabal configure -w ghc-8.10.7 - 8_10_7-check: | cd example.org cabal check diff --git a/fixtures/sourcehut-parallel.sourcehut b/fixtures/sourcehut-parallel.sourcehut index ee3b4eaa..56e5faac 100644 --- a/fixtures/sourcehut-parallel.sourcehut +++ b/fixtures/sourcehut-parallel.sourcehut @@ -16,7 +16,7 @@ image: ubuntu/bionic packages: - gcc - - cabal-install-3.4 + - libgmp-dev - ghc-7.10.1 repositories: hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 @@ -24,12 +24,18 @@ sources: - https://example.org tasks: - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + mkdir -p "$HOME/.ghcup/bin" + curl -sL https://downloads.haskell.org/ghcup/0.1.17.8/x86_64-linux-ghcup-0.1.17.8 > "$HOME/.ghcup/bin/ghcup" + chmod a+x "$HOME/.ghcup/bin/ghcup" + export PATH=$PATH:$HOME/.ghcup/bin + echo "export PATH=$PATH:$HOME/.ghcup/bin" >> ~/.buildenv + "$HOME/.ghcup/bin/ghcup" install cabal 3.6 + export PATH=$PATH:/opt/ghc/bin + echo "export PATH=$PATH:/opt/ghc/bin" >> ~/.buildenv cabal update - 7_10_1-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.10.1 + cabal configure -w ghc-7.10.1 - 7_10_1-check: | cd example.org cabal check @@ -66,7 +72,7 @@ triggers: image: ubuntu/bionic packages: - gcc - - cabal-install-3.4 + - libgmp-dev - ghc-7.10.2 repositories: hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 @@ -74,12 +80,18 @@ sources: - https://example.org tasks: - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + mkdir -p "$HOME/.ghcup/bin" + curl -sL https://downloads.haskell.org/ghcup/0.1.17.8/x86_64-linux-ghcup-0.1.17.8 > "$HOME/.ghcup/bin/ghcup" + chmod a+x "$HOME/.ghcup/bin/ghcup" + export PATH=$PATH:$HOME/.ghcup/bin + echo "export PATH=$PATH:$HOME/.ghcup/bin" >> ~/.buildenv + "$HOME/.ghcup/bin/ghcup" install cabal 3.6 + export PATH=$PATH:/opt/ghc/bin + echo "export PATH=$PATH:/opt/ghc/bin" >> ~/.buildenv cabal update - 7_10_2-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.10.2 + cabal configure -w ghc-7.10.2 - 7_10_2-check: | cd example.org cabal check @@ -116,7 +128,7 @@ triggers: image: ubuntu/bionic packages: - gcc - - cabal-install-3.4 + - libgmp-dev - ghc-7.10.3 repositories: hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 @@ -124,12 +136,18 @@ sources: - https://example.org tasks: - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + mkdir -p "$HOME/.ghcup/bin" + curl -sL https://downloads.haskell.org/ghcup/0.1.17.8/x86_64-linux-ghcup-0.1.17.8 > "$HOME/.ghcup/bin/ghcup" + chmod a+x "$HOME/.ghcup/bin/ghcup" + export PATH=$PATH:$HOME/.ghcup/bin + echo "export PATH=$PATH:$HOME/.ghcup/bin" >> ~/.buildenv + "$HOME/.ghcup/bin/ghcup" install cabal 3.6 + export PATH=$PATH:/opt/ghc/bin + echo "export PATH=$PATH:/opt/ghc/bin" >> ~/.buildenv cabal update - 7_10_3-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.10.3 + cabal configure -w ghc-7.10.3 - 7_10_3-check: | cd example.org cabal check @@ -166,7 +184,7 @@ triggers: image: ubuntu/bionic packages: - gcc - - cabal-install-3.4 + - libgmp-dev - ghc-7.8.1 repositories: hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 @@ -174,12 +192,18 @@ sources: - https://example.org tasks: - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + mkdir -p "$HOME/.ghcup/bin" + curl -sL https://downloads.haskell.org/ghcup/0.1.17.8/x86_64-linux-ghcup-0.1.17.8 > "$HOME/.ghcup/bin/ghcup" + chmod a+x "$HOME/.ghcup/bin/ghcup" + export PATH=$PATH:$HOME/.ghcup/bin + echo "export PATH=$PATH:$HOME/.ghcup/bin" >> ~/.buildenv + "$HOME/.ghcup/bin/ghcup" install cabal 3.6 + export PATH=$PATH:/opt/ghc/bin + echo "export PATH=$PATH:/opt/ghc/bin" >> ~/.buildenv cabal update - 7_8_1-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.8.1 + cabal configure -w ghc-7.8.1 - 7_8_1-check: | cd example.org cabal check @@ -216,7 +240,7 @@ triggers: image: ubuntu/bionic packages: - gcc - - cabal-install-3.4 + - libgmp-dev - ghc-7.8.2 repositories: hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 @@ -224,12 +248,18 @@ sources: - https://example.org tasks: - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + mkdir -p "$HOME/.ghcup/bin" + curl -sL https://downloads.haskell.org/ghcup/0.1.17.8/x86_64-linux-ghcup-0.1.17.8 > "$HOME/.ghcup/bin/ghcup" + chmod a+x "$HOME/.ghcup/bin/ghcup" + export PATH=$PATH:$HOME/.ghcup/bin + echo "export PATH=$PATH:$HOME/.ghcup/bin" >> ~/.buildenv + "$HOME/.ghcup/bin/ghcup" install cabal 3.6 + export PATH=$PATH:/opt/ghc/bin + echo "export PATH=$PATH:/opt/ghc/bin" >> ~/.buildenv cabal update - 7_8_2-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.8.2 + cabal configure -w ghc-7.8.2 - 7_8_2-check: | cd example.org cabal check @@ -266,7 +296,7 @@ triggers: image: ubuntu/bionic packages: - gcc - - cabal-install-3.4 + - libgmp-dev - ghc-7.8.3 repositories: hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 @@ -274,12 +304,18 @@ sources: - https://example.org tasks: - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + mkdir -p "$HOME/.ghcup/bin" + curl -sL https://downloads.haskell.org/ghcup/0.1.17.8/x86_64-linux-ghcup-0.1.17.8 > "$HOME/.ghcup/bin/ghcup" + chmod a+x "$HOME/.ghcup/bin/ghcup" + export PATH=$PATH:$HOME/.ghcup/bin + echo "export PATH=$PATH:$HOME/.ghcup/bin" >> ~/.buildenv + "$HOME/.ghcup/bin/ghcup" install cabal 3.6 + export PATH=$PATH:/opt/ghc/bin + echo "export PATH=$PATH:/opt/ghc/bin" >> ~/.buildenv cabal update - 7_8_3-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.8.3 + cabal configure -w ghc-7.8.3 - 7_8_3-check: | cd example.org cabal check @@ -316,7 +352,7 @@ triggers: image: ubuntu/bionic packages: - gcc - - cabal-install-3.4 + - libgmp-dev - ghc-7.8.4 repositories: hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 @@ -324,12 +360,18 @@ sources: - https://example.org tasks: - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + mkdir -p "$HOME/.ghcup/bin" + curl -sL https://downloads.haskell.org/ghcup/0.1.17.8/x86_64-linux-ghcup-0.1.17.8 > "$HOME/.ghcup/bin/ghcup" + chmod a+x "$HOME/.ghcup/bin/ghcup" + export PATH=$PATH:$HOME/.ghcup/bin + echo "export PATH=$PATH:$HOME/.ghcup/bin" >> ~/.buildenv + "$HOME/.ghcup/bin/ghcup" install cabal 3.6 + export PATH=$PATH:/opt/ghc/bin + echo "export PATH=$PATH:/opt/ghc/bin" >> ~/.buildenv cabal update - 7_8_4-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.8.4 + cabal configure -w ghc-7.8.4 - 7_8_4-check: | cd example.org cabal check @@ -366,7 +408,7 @@ triggers: image: ubuntu/bionic packages: - gcc - - cabal-install-3.4 + - libgmp-dev - ghc-8.0.1 repositories: hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 @@ -374,12 +416,18 @@ sources: - https://example.org tasks: - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + mkdir -p "$HOME/.ghcup/bin" + curl -sL https://downloads.haskell.org/ghcup/0.1.17.8/x86_64-linux-ghcup-0.1.17.8 > "$HOME/.ghcup/bin/ghcup" + chmod a+x "$HOME/.ghcup/bin/ghcup" + export PATH=$PATH:$HOME/.ghcup/bin + echo "export PATH=$PATH:$HOME/.ghcup/bin" >> ~/.buildenv + "$HOME/.ghcup/bin/ghcup" install cabal 3.6 + export PATH=$PATH:/opt/ghc/bin + echo "export PATH=$PATH:/opt/ghc/bin" >> ~/.buildenv cabal update - 8_0_1-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.0.1 + cabal configure -w ghc-8.0.1 - 8_0_1-check: | cd example.org cabal check @@ -416,7 +464,7 @@ triggers: image: ubuntu/bionic packages: - gcc - - cabal-install-3.4 + - libgmp-dev - ghc-8.0.2 repositories: hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 @@ -424,12 +472,18 @@ sources: - https://example.org tasks: - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + mkdir -p "$HOME/.ghcup/bin" + curl -sL https://downloads.haskell.org/ghcup/0.1.17.8/x86_64-linux-ghcup-0.1.17.8 > "$HOME/.ghcup/bin/ghcup" + chmod a+x "$HOME/.ghcup/bin/ghcup" + export PATH=$PATH:$HOME/.ghcup/bin + echo "export PATH=$PATH:$HOME/.ghcup/bin" >> ~/.buildenv + "$HOME/.ghcup/bin/ghcup" install cabal 3.6 + export PATH=$PATH:/opt/ghc/bin + echo "export PATH=$PATH:/opt/ghc/bin" >> ~/.buildenv cabal update - 8_0_2-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.0.2 + cabal configure -w ghc-8.0.2 - 8_0_2-check: | cd example.org cabal check @@ -466,7 +520,7 @@ triggers: image: ubuntu/bionic packages: - gcc - - cabal-install-3.4 + - libgmp-dev - ghc-8.10.1 repositories: hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 @@ -474,12 +528,18 @@ sources: - https://example.org tasks: - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + mkdir -p "$HOME/.ghcup/bin" + curl -sL https://downloads.haskell.org/ghcup/0.1.17.8/x86_64-linux-ghcup-0.1.17.8 > "$HOME/.ghcup/bin/ghcup" + chmod a+x "$HOME/.ghcup/bin/ghcup" + export PATH=$PATH:$HOME/.ghcup/bin + echo "export PATH=$PATH:$HOME/.ghcup/bin" >> ~/.buildenv + "$HOME/.ghcup/bin/ghcup" install cabal 3.6 + export PATH=$PATH:/opt/ghc/bin + echo "export PATH=$PATH:/opt/ghc/bin" >> ~/.buildenv cabal update - 8_10_1-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.1 + cabal configure -w ghc-8.10.1 - 8_10_1-check: | cd example.org cabal check @@ -516,7 +576,7 @@ triggers: image: ubuntu/bionic packages: - gcc - - cabal-install-3.4 + - libgmp-dev - ghc-8.10.2 repositories: hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 @@ -524,12 +584,18 @@ sources: - https://example.org tasks: - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + mkdir -p "$HOME/.ghcup/bin" + curl -sL https://downloads.haskell.org/ghcup/0.1.17.8/x86_64-linux-ghcup-0.1.17.8 > "$HOME/.ghcup/bin/ghcup" + chmod a+x "$HOME/.ghcup/bin/ghcup" + export PATH=$PATH:$HOME/.ghcup/bin + echo "export PATH=$PATH:$HOME/.ghcup/bin" >> ~/.buildenv + "$HOME/.ghcup/bin/ghcup" install cabal 3.6 + export PATH=$PATH:/opt/ghc/bin + echo "export PATH=$PATH:/opt/ghc/bin" >> ~/.buildenv cabal update - 8_10_2-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.2 + cabal configure -w ghc-8.10.2 - 8_10_2-check: | cd example.org cabal check @@ -566,7 +632,7 @@ triggers: image: ubuntu/bionic packages: - gcc - - cabal-install-3.4 + - libgmp-dev - ghc-8.10.3 repositories: hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 @@ -574,12 +640,18 @@ sources: - https://example.org tasks: - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + mkdir -p "$HOME/.ghcup/bin" + curl -sL https://downloads.haskell.org/ghcup/0.1.17.8/x86_64-linux-ghcup-0.1.17.8 > "$HOME/.ghcup/bin/ghcup" + chmod a+x "$HOME/.ghcup/bin/ghcup" + export PATH=$PATH:$HOME/.ghcup/bin + echo "export PATH=$PATH:$HOME/.ghcup/bin" >> ~/.buildenv + "$HOME/.ghcup/bin/ghcup" install cabal 3.6 + export PATH=$PATH:/opt/ghc/bin + echo "export PATH=$PATH:/opt/ghc/bin" >> ~/.buildenv cabal update - 8_10_3-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.3 + cabal configure -w ghc-8.10.3 - 8_10_3-check: | cd example.org cabal check @@ -616,7 +688,7 @@ triggers: image: ubuntu/bionic packages: - gcc - - cabal-install-3.4 + - libgmp-dev - ghc-8.10.4 repositories: hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 @@ -624,12 +696,18 @@ sources: - https://example.org tasks: - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + mkdir -p "$HOME/.ghcup/bin" + curl -sL https://downloads.haskell.org/ghcup/0.1.17.8/x86_64-linux-ghcup-0.1.17.8 > "$HOME/.ghcup/bin/ghcup" + chmod a+x "$HOME/.ghcup/bin/ghcup" + export PATH=$PATH:$HOME/.ghcup/bin + echo "export PATH=$PATH:$HOME/.ghcup/bin" >> ~/.buildenv + "$HOME/.ghcup/bin/ghcup" install cabal 3.6 + export PATH=$PATH:/opt/ghc/bin + echo "export PATH=$PATH:/opt/ghc/bin" >> ~/.buildenv cabal update - 8_10_4-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.4 + cabal configure -w ghc-8.10.4 - 8_10_4-check: | cd example.org cabal check @@ -666,20 +744,22 @@ triggers: image: ubuntu/bionic packages: - gcc - - cabal-install-3.4 - - ghc-8.10.5 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 + - libgmp-dev sources: - https://example.org tasks: - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + mkdir -p "$HOME/.ghcup/bin" + curl -sL https://downloads.haskell.org/ghcup/0.1.17.8/x86_64-linux-ghcup-0.1.17.8 > "$HOME/.ghcup/bin/ghcup" + chmod a+x "$HOME/.ghcup/bin/ghcup" + export PATH=$PATH:$HOME/.ghcup/bin + echo "export PATH=$PATH:$HOME/.ghcup/bin" >> ~/.buildenv + "$HOME/.ghcup/bin/ghcup" install cabal 3.6 + "$HOME/.ghcup/bin/ghcup" install ghc "ghc-8.10.5" cabal update - 8_10_5-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.5 + cabal configure -w ghc-8.10.5 - 8_10_5-check: | cd example.org cabal check @@ -716,20 +796,22 @@ triggers: image: ubuntu/bionic packages: - gcc - - cabal-install-3.4 - - ghc-8.10.6 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 + - libgmp-dev sources: - https://example.org tasks: - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + mkdir -p "$HOME/.ghcup/bin" + curl -sL https://downloads.haskell.org/ghcup/0.1.17.8/x86_64-linux-ghcup-0.1.17.8 > "$HOME/.ghcup/bin/ghcup" + chmod a+x "$HOME/.ghcup/bin/ghcup" + export PATH=$PATH:$HOME/.ghcup/bin + echo "export PATH=$PATH:$HOME/.ghcup/bin" >> ~/.buildenv + "$HOME/.ghcup/bin/ghcup" install cabal 3.6 + "$HOME/.ghcup/bin/ghcup" install ghc "ghc-8.10.6" cabal update - 8_10_6-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.6 + cabal configure -w ghc-8.10.6 - 8_10_6-check: | cd example.org cabal check @@ -766,20 +848,22 @@ triggers: image: ubuntu/bionic packages: - gcc - - cabal-install-3.4 - - ghc-8.10.7 -repositories: - hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 + - libgmp-dev sources: - https://example.org tasks: - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + mkdir -p "$HOME/.ghcup/bin" + curl -sL https://downloads.haskell.org/ghcup/0.1.17.8/x86_64-linux-ghcup-0.1.17.8 > "$HOME/.ghcup/bin/ghcup" + chmod a+x "$HOME/.ghcup/bin/ghcup" + export PATH=$PATH:$HOME/.ghcup/bin + echo "export PATH=$PATH:$HOME/.ghcup/bin" >> ~/.buildenv + "$HOME/.ghcup/bin/ghcup" install cabal 3.6 + "$HOME/.ghcup/bin/ghcup" install ghc "ghc-8.10.7" cabal update - 8_10_7-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.7 + cabal configure -w ghc-8.10.7 - 8_10_7-check: | cd example.org cabal check @@ -816,7 +900,7 @@ triggers: image: ubuntu/bionic packages: - gcc - - cabal-install-3.4 + - libgmp-dev - ghc-8.2.1 repositories: hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 @@ -824,12 +908,18 @@ sources: - https://example.org tasks: - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + mkdir -p "$HOME/.ghcup/bin" + curl -sL https://downloads.haskell.org/ghcup/0.1.17.8/x86_64-linux-ghcup-0.1.17.8 > "$HOME/.ghcup/bin/ghcup" + chmod a+x "$HOME/.ghcup/bin/ghcup" + export PATH=$PATH:$HOME/.ghcup/bin + echo "export PATH=$PATH:$HOME/.ghcup/bin" >> ~/.buildenv + "$HOME/.ghcup/bin/ghcup" install cabal 3.6 + export PATH=$PATH:/opt/ghc/bin + echo "export PATH=$PATH:/opt/ghc/bin" >> ~/.buildenv cabal update - 8_2_1-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.2.1 + cabal configure -w ghc-8.2.1 - 8_2_1-check: | cd example.org cabal check @@ -866,7 +956,7 @@ triggers: image: ubuntu/bionic packages: - gcc - - cabal-install-3.4 + - libgmp-dev - ghc-8.2.2 repositories: hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 @@ -874,12 +964,18 @@ sources: - https://example.org tasks: - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + mkdir -p "$HOME/.ghcup/bin" + curl -sL https://downloads.haskell.org/ghcup/0.1.17.8/x86_64-linux-ghcup-0.1.17.8 > "$HOME/.ghcup/bin/ghcup" + chmod a+x "$HOME/.ghcup/bin/ghcup" + export PATH=$PATH:$HOME/.ghcup/bin + echo "export PATH=$PATH:$HOME/.ghcup/bin" >> ~/.buildenv + "$HOME/.ghcup/bin/ghcup" install cabal 3.6 + export PATH=$PATH:/opt/ghc/bin + echo "export PATH=$PATH:/opt/ghc/bin" >> ~/.buildenv cabal update - 8_2_2-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.2.2 + cabal configure -w ghc-8.2.2 - 8_2_2-check: | cd example.org cabal check @@ -916,7 +1012,7 @@ triggers: image: ubuntu/bionic packages: - gcc - - cabal-install-3.4 + - libgmp-dev - ghc-8.4.1 repositories: hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 @@ -924,12 +1020,18 @@ sources: - https://example.org tasks: - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + mkdir -p "$HOME/.ghcup/bin" + curl -sL https://downloads.haskell.org/ghcup/0.1.17.8/x86_64-linux-ghcup-0.1.17.8 > "$HOME/.ghcup/bin/ghcup" + chmod a+x "$HOME/.ghcup/bin/ghcup" + export PATH=$PATH:$HOME/.ghcup/bin + echo "export PATH=$PATH:$HOME/.ghcup/bin" >> ~/.buildenv + "$HOME/.ghcup/bin/ghcup" install cabal 3.6 + export PATH=$PATH:/opt/ghc/bin + echo "export PATH=$PATH:/opt/ghc/bin" >> ~/.buildenv cabal update - 8_4_1-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.4.1 + cabal configure -w ghc-8.4.1 - 8_4_1-check: | cd example.org cabal check @@ -966,7 +1068,7 @@ triggers: image: ubuntu/bionic packages: - gcc - - cabal-install-3.4 + - libgmp-dev - ghc-8.4.2 repositories: hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 @@ -974,12 +1076,18 @@ sources: - https://example.org tasks: - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + mkdir -p "$HOME/.ghcup/bin" + curl -sL https://downloads.haskell.org/ghcup/0.1.17.8/x86_64-linux-ghcup-0.1.17.8 > "$HOME/.ghcup/bin/ghcup" + chmod a+x "$HOME/.ghcup/bin/ghcup" + export PATH=$PATH:$HOME/.ghcup/bin + echo "export PATH=$PATH:$HOME/.ghcup/bin" >> ~/.buildenv + "$HOME/.ghcup/bin/ghcup" install cabal 3.6 + export PATH=$PATH:/opt/ghc/bin + echo "export PATH=$PATH:/opt/ghc/bin" >> ~/.buildenv cabal update - 8_4_2-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.4.2 + cabal configure -w ghc-8.4.2 - 8_4_2-check: | cd example.org cabal check @@ -1016,7 +1124,7 @@ triggers: image: ubuntu/bionic packages: - gcc - - cabal-install-3.4 + - libgmp-dev - ghc-8.4.3 repositories: hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 @@ -1024,12 +1132,18 @@ sources: - https://example.org tasks: - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + mkdir -p "$HOME/.ghcup/bin" + curl -sL https://downloads.haskell.org/ghcup/0.1.17.8/x86_64-linux-ghcup-0.1.17.8 > "$HOME/.ghcup/bin/ghcup" + chmod a+x "$HOME/.ghcup/bin/ghcup" + export PATH=$PATH:$HOME/.ghcup/bin + echo "export PATH=$PATH:$HOME/.ghcup/bin" >> ~/.buildenv + "$HOME/.ghcup/bin/ghcup" install cabal 3.6 + export PATH=$PATH:/opt/ghc/bin + echo "export PATH=$PATH:/opt/ghc/bin" >> ~/.buildenv cabal update - 8_4_3-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.4.3 + cabal configure -w ghc-8.4.3 - 8_4_3-check: | cd example.org cabal check @@ -1066,7 +1180,7 @@ triggers: image: ubuntu/bionic packages: - gcc - - cabal-install-3.4 + - libgmp-dev - ghc-8.4.4 repositories: hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 @@ -1074,12 +1188,18 @@ sources: - https://example.org tasks: - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + mkdir -p "$HOME/.ghcup/bin" + curl -sL https://downloads.haskell.org/ghcup/0.1.17.8/x86_64-linux-ghcup-0.1.17.8 > "$HOME/.ghcup/bin/ghcup" + chmod a+x "$HOME/.ghcup/bin/ghcup" + export PATH=$PATH:$HOME/.ghcup/bin + echo "export PATH=$PATH:$HOME/.ghcup/bin" >> ~/.buildenv + "$HOME/.ghcup/bin/ghcup" install cabal 3.6 + export PATH=$PATH:/opt/ghc/bin + echo "export PATH=$PATH:/opt/ghc/bin" >> ~/.buildenv cabal update - 8_4_4-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.4.4 + cabal configure -w ghc-8.4.4 - 8_4_4-check: | cd example.org cabal check @@ -1116,7 +1236,7 @@ triggers: image: ubuntu/bionic packages: - gcc - - cabal-install-3.4 + - libgmp-dev - ghc-8.6.1 repositories: hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 @@ -1124,12 +1244,18 @@ sources: - https://example.org tasks: - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + mkdir -p "$HOME/.ghcup/bin" + curl -sL https://downloads.haskell.org/ghcup/0.1.17.8/x86_64-linux-ghcup-0.1.17.8 > "$HOME/.ghcup/bin/ghcup" + chmod a+x "$HOME/.ghcup/bin/ghcup" + export PATH=$PATH:$HOME/.ghcup/bin + echo "export PATH=$PATH:$HOME/.ghcup/bin" >> ~/.buildenv + "$HOME/.ghcup/bin/ghcup" install cabal 3.6 + export PATH=$PATH:/opt/ghc/bin + echo "export PATH=$PATH:/opt/ghc/bin" >> ~/.buildenv cabal update - 8_6_1-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.6.1 + cabal configure -w ghc-8.6.1 - 8_6_1-check: | cd example.org cabal check @@ -1166,7 +1292,7 @@ triggers: image: ubuntu/bionic packages: - gcc - - cabal-install-3.4 + - libgmp-dev - ghc-8.6.2 repositories: hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 @@ -1174,12 +1300,18 @@ sources: - https://example.org tasks: - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + mkdir -p "$HOME/.ghcup/bin" + curl -sL https://downloads.haskell.org/ghcup/0.1.17.8/x86_64-linux-ghcup-0.1.17.8 > "$HOME/.ghcup/bin/ghcup" + chmod a+x "$HOME/.ghcup/bin/ghcup" + export PATH=$PATH:$HOME/.ghcup/bin + echo "export PATH=$PATH:$HOME/.ghcup/bin" >> ~/.buildenv + "$HOME/.ghcup/bin/ghcup" install cabal 3.6 + export PATH=$PATH:/opt/ghc/bin + echo "export PATH=$PATH:/opt/ghc/bin" >> ~/.buildenv cabal update - 8_6_2-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.6.2 + cabal configure -w ghc-8.6.2 - 8_6_2-check: | cd example.org cabal check @@ -1216,7 +1348,7 @@ triggers: image: ubuntu/bionic packages: - gcc - - cabal-install-3.4 + - libgmp-dev - ghc-8.6.3 repositories: hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 @@ -1224,12 +1356,18 @@ sources: - https://example.org tasks: - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + mkdir -p "$HOME/.ghcup/bin" + curl -sL https://downloads.haskell.org/ghcup/0.1.17.8/x86_64-linux-ghcup-0.1.17.8 > "$HOME/.ghcup/bin/ghcup" + chmod a+x "$HOME/.ghcup/bin/ghcup" + export PATH=$PATH:$HOME/.ghcup/bin + echo "export PATH=$PATH:$HOME/.ghcup/bin" >> ~/.buildenv + "$HOME/.ghcup/bin/ghcup" install cabal 3.6 + export PATH=$PATH:/opt/ghc/bin + echo "export PATH=$PATH:/opt/ghc/bin" >> ~/.buildenv cabal update - 8_6_3-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.6.3 + cabal configure -w ghc-8.6.3 - 8_6_3-check: | cd example.org cabal check @@ -1266,7 +1404,7 @@ triggers: image: ubuntu/bionic packages: - gcc - - cabal-install-3.4 + - libgmp-dev - ghc-8.6.4 repositories: hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 @@ -1274,12 +1412,18 @@ sources: - https://example.org tasks: - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + mkdir -p "$HOME/.ghcup/bin" + curl -sL https://downloads.haskell.org/ghcup/0.1.17.8/x86_64-linux-ghcup-0.1.17.8 > "$HOME/.ghcup/bin/ghcup" + chmod a+x "$HOME/.ghcup/bin/ghcup" + export PATH=$PATH:$HOME/.ghcup/bin + echo "export PATH=$PATH:$HOME/.ghcup/bin" >> ~/.buildenv + "$HOME/.ghcup/bin/ghcup" install cabal 3.6 + export PATH=$PATH:/opt/ghc/bin + echo "export PATH=$PATH:/opt/ghc/bin" >> ~/.buildenv cabal update - 8_6_4-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.6.4 + cabal configure -w ghc-8.6.4 - 8_6_4-check: | cd example.org cabal check @@ -1316,7 +1460,7 @@ triggers: image: ubuntu/bionic packages: - gcc - - cabal-install-3.4 + - libgmp-dev - ghc-8.6.5 repositories: hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 @@ -1324,12 +1468,18 @@ sources: - https://example.org tasks: - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + mkdir -p "$HOME/.ghcup/bin" + curl -sL https://downloads.haskell.org/ghcup/0.1.17.8/x86_64-linux-ghcup-0.1.17.8 > "$HOME/.ghcup/bin/ghcup" + chmod a+x "$HOME/.ghcup/bin/ghcup" + export PATH=$PATH:$HOME/.ghcup/bin + echo "export PATH=$PATH:$HOME/.ghcup/bin" >> ~/.buildenv + "$HOME/.ghcup/bin/ghcup" install cabal 3.6 + export PATH=$PATH:/opt/ghc/bin + echo "export PATH=$PATH:/opt/ghc/bin" >> ~/.buildenv cabal update - 8_6_5-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.6.5 + cabal configure -w ghc-8.6.5 - 8_6_5-check: | cd example.org cabal check @@ -1366,7 +1516,7 @@ triggers: image: ubuntu/bionic packages: - gcc - - cabal-install-3.4 + - libgmp-dev - ghc-8.8.1 repositories: hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 @@ -1374,12 +1524,18 @@ sources: - https://example.org tasks: - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + mkdir -p "$HOME/.ghcup/bin" + curl -sL https://downloads.haskell.org/ghcup/0.1.17.8/x86_64-linux-ghcup-0.1.17.8 > "$HOME/.ghcup/bin/ghcup" + chmod a+x "$HOME/.ghcup/bin/ghcup" + export PATH=$PATH:$HOME/.ghcup/bin + echo "export PATH=$PATH:$HOME/.ghcup/bin" >> ~/.buildenv + "$HOME/.ghcup/bin/ghcup" install cabal 3.6 + export PATH=$PATH:/opt/ghc/bin + echo "export PATH=$PATH:/opt/ghc/bin" >> ~/.buildenv cabal update - 8_8_1-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.8.1 + cabal configure -w ghc-8.8.1 - 8_8_1-check: | cd example.org cabal check @@ -1416,7 +1572,7 @@ triggers: image: ubuntu/bionic packages: - gcc - - cabal-install-3.4 + - libgmp-dev - ghc-8.8.2 repositories: hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 @@ -1424,12 +1580,18 @@ sources: - https://example.org tasks: - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + mkdir -p "$HOME/.ghcup/bin" + curl -sL https://downloads.haskell.org/ghcup/0.1.17.8/x86_64-linux-ghcup-0.1.17.8 > "$HOME/.ghcup/bin/ghcup" + chmod a+x "$HOME/.ghcup/bin/ghcup" + export PATH=$PATH:$HOME/.ghcup/bin + echo "export PATH=$PATH:$HOME/.ghcup/bin" >> ~/.buildenv + "$HOME/.ghcup/bin/ghcup" install cabal 3.6 + export PATH=$PATH:/opt/ghc/bin + echo "export PATH=$PATH:/opt/ghc/bin" >> ~/.buildenv cabal update - 8_8_2-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.8.2 + cabal configure -w ghc-8.8.2 - 8_8_2-check: | cd example.org cabal check @@ -1466,7 +1628,7 @@ triggers: image: ubuntu/bionic packages: - gcc - - cabal-install-3.4 + - libgmp-dev - ghc-8.8.3 repositories: hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 @@ -1474,12 +1636,18 @@ sources: - https://example.org tasks: - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + mkdir -p "$HOME/.ghcup/bin" + curl -sL https://downloads.haskell.org/ghcup/0.1.17.8/x86_64-linux-ghcup-0.1.17.8 > "$HOME/.ghcup/bin/ghcup" + chmod a+x "$HOME/.ghcup/bin/ghcup" + export PATH=$PATH:$HOME/.ghcup/bin + echo "export PATH=$PATH:$HOME/.ghcup/bin" >> ~/.buildenv + "$HOME/.ghcup/bin/ghcup" install cabal 3.6 + export PATH=$PATH:/opt/ghc/bin + echo "export PATH=$PATH:/opt/ghc/bin" >> ~/.buildenv cabal update - 8_8_3-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.8.3 + cabal configure -w ghc-8.8.3 - 8_8_3-check: | cd example.org cabal check @@ -1516,7 +1684,7 @@ triggers: image: ubuntu/bionic packages: - gcc - - cabal-install-3.4 + - libgmp-dev - ghc-8.8.4 repositories: hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 @@ -1524,12 +1692,18 @@ sources: - https://example.org tasks: - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + mkdir -p "$HOME/.ghcup/bin" + curl -sL https://downloads.haskell.org/ghcup/0.1.17.8/x86_64-linux-ghcup-0.1.17.8 > "$HOME/.ghcup/bin/ghcup" + chmod a+x "$HOME/.ghcup/bin/ghcup" + export PATH=$PATH:$HOME/.ghcup/bin + echo "export PATH=$PATH:$HOME/.ghcup/bin" >> ~/.buildenv + "$HOME/.ghcup/bin/ghcup" install cabal 3.6 + export PATH=$PATH:/opt/ghc/bin + echo "export PATH=$PATH:/opt/ghc/bin" >> ~/.buildenv cabal update - 8_8_4-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.8.4 + cabal configure -w ghc-8.8.4 - 8_8_4-check: | cd example.org cabal check diff --git a/fixtures/travis-patch.sourcehut b/fixtures/travis-patch.sourcehut index 320dee02..3aef2005 100644 --- a/fixtures/travis-patch.sourcehut +++ b/fixtures/travis-patch.sourcehut @@ -16,7 +16,7 @@ image: ubuntu/bionic packages: - gcc - - cabal-install-3.4 + - libgmp-dev - ghc-7.8.1 - ghc-7.8.2 - ghc-7.8.3 @@ -45,21 +45,27 @@ packages: - ghc-8.10.2 - ghc-8.10.3 - ghc-8.10.4 - - ghc-8.10.5 - - ghc-8.10.6 - - ghc-8.10.7 repositories: hvr-ghc: http://ppa.launchpad.net/hvr/ghc/ubuntu bionic main ff3aeacef6f88286 sources: - https://example.org tasks: - all-prepare: | - export PATH=$PATH:/opt/cabal/bin - echo "export PATH=$PATH:/opt/cabal/bin" >> ~/.buildenv + mkdir -p "$HOME/.ghcup/bin" + curl -sL https://downloads.haskell.org/ghcup/0.1.17.8/x86_64-linux-ghcup-0.1.17.8 > "$HOME/.ghcup/bin/ghcup" + chmod a+x "$HOME/.ghcup/bin/ghcup" + export PATH=$PATH:$HOME/.ghcup/bin + echo "export PATH=$PATH:$HOME/.ghcup/bin" >> ~/.buildenv + "$HOME/.ghcup/bin/ghcup" install cabal 3.6 + "$HOME/.ghcup/bin/ghcup" install ghc "ghc-8.10.5" + "$HOME/.ghcup/bin/ghcup" install ghc "ghc-8.10.6" + "$HOME/.ghcup/bin/ghcup" install ghc "ghc-8.10.7" + export PATH=$PATH:/opt/ghc/bin + echo "export PATH=$PATH:/opt/ghc/bin" >> ~/.buildenv cabal update - 7_8_1-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.8.1 + cabal configure -w ghc-7.8.1 - 7_8_1-check: | cd example.org cabal check @@ -78,7 +84,7 @@ tasks: cabal haddock all - 7_8_2-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.8.2 + cabal configure -w ghc-7.8.2 - 7_8_2-check: | cd example.org cabal check @@ -97,7 +103,7 @@ tasks: cabal haddock all - 7_8_3-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.8.3 + cabal configure -w ghc-7.8.3 - 7_8_3-check: | cd example.org cabal check @@ -116,7 +122,7 @@ tasks: cabal haddock all - 7_8_4-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.8.4 + cabal configure -w ghc-7.8.4 - 7_8_4-check: | cd example.org cabal check @@ -135,7 +141,7 @@ tasks: cabal haddock all - 7_10_1-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.10.1 + cabal configure -w ghc-7.10.1 - 7_10_1-check: | cd example.org cabal check @@ -154,7 +160,7 @@ tasks: cabal haddock all - 7_10_2-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.10.2 + cabal configure -w ghc-7.10.2 - 7_10_2-check: | cd example.org cabal check @@ -173,7 +179,7 @@ tasks: cabal haddock all - 7_10_3-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-7.10.3 + cabal configure -w ghc-7.10.3 - 7_10_3-check: | cd example.org cabal check @@ -192,7 +198,7 @@ tasks: cabal haddock all - 8_0_1-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.0.1 + cabal configure -w ghc-8.0.1 - 8_0_1-check: | cd example.org cabal check @@ -211,7 +217,7 @@ tasks: cabal haddock all - 8_0_2-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.0.2 + cabal configure -w ghc-8.0.2 - 8_0_2-check: | cd example.org cabal check @@ -230,7 +236,7 @@ tasks: cabal haddock all - 8_2_1-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.2.1 + cabal configure -w ghc-8.2.1 - 8_2_1-check: | cd example.org cabal check @@ -249,7 +255,7 @@ tasks: cabal haddock all - 8_2_2-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.2.2 + cabal configure -w ghc-8.2.2 - 8_2_2-check: | cd example.org cabal check @@ -268,7 +274,7 @@ tasks: cabal haddock all - 8_4_1-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.4.1 + cabal configure -w ghc-8.4.1 - 8_4_1-check: | cd example.org cabal check @@ -287,7 +293,7 @@ tasks: cabal haddock all - 8_4_2-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.4.2 + cabal configure -w ghc-8.4.2 - 8_4_2-check: | cd example.org cabal check @@ -306,7 +312,7 @@ tasks: cabal haddock all - 8_4_3-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.4.3 + cabal configure -w ghc-8.4.3 - 8_4_3-check: | cd example.org cabal check @@ -325,7 +331,7 @@ tasks: cabal haddock all - 8_4_4-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.4.4 + cabal configure -w ghc-8.4.4 - 8_4_4-check: | cd example.org cabal check @@ -344,7 +350,7 @@ tasks: cabal haddock all - 8_6_1-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.6.1 + cabal configure -w ghc-8.6.1 - 8_6_1-check: | cd example.org cabal check @@ -363,7 +369,7 @@ tasks: cabal haddock all - 8_6_2-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.6.2 + cabal configure -w ghc-8.6.2 - 8_6_2-check: | cd example.org cabal check @@ -382,7 +388,7 @@ tasks: cabal haddock all - 8_6_3-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.6.3 + cabal configure -w ghc-8.6.3 - 8_6_3-check: | cd example.org cabal check @@ -401,7 +407,7 @@ tasks: cabal haddock all - 8_6_4-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.6.4 + cabal configure -w ghc-8.6.4 - 8_6_4-check: | cd example.org cabal check @@ -420,7 +426,7 @@ tasks: cabal haddock all - 8_6_5-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.6.5 + cabal configure -w ghc-8.6.5 - 8_6_5-check: | cd example.org cabal check @@ -439,7 +445,7 @@ tasks: cabal haddock all - 8_8_1-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.8.1 + cabal configure -w ghc-8.8.1 - 8_8_1-check: | cd example.org cabal check @@ -458,7 +464,7 @@ tasks: cabal haddock all - 8_8_2-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.8.2 + cabal configure -w ghc-8.8.2 - 8_8_2-check: | cd example.org cabal check @@ -477,7 +483,7 @@ tasks: cabal haddock all - 8_8_3-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.8.3 + cabal configure -w ghc-8.8.3 - 8_8_3-check: | cd example.org cabal check @@ -496,7 +502,7 @@ tasks: cabal haddock all - 8_8_4-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.8.4 + cabal configure -w ghc-8.8.4 - 8_8_4-check: | cd example.org cabal check @@ -515,7 +521,7 @@ tasks: cabal haddock all - 8_10_1-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.1 + cabal configure -w ghc-8.10.1 - 8_10_1-check: | cd example.org cabal check @@ -534,7 +540,7 @@ tasks: cabal haddock all - 8_10_2-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.2 + cabal configure -w ghc-8.10.2 - 8_10_2-check: | cd example.org cabal check @@ -553,7 +559,7 @@ tasks: cabal haddock all - 8_10_3-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.3 + cabal configure -w ghc-8.10.3 - 8_10_3-check: | cd example.org cabal check @@ -572,7 +578,7 @@ tasks: cabal haddock all - 8_10_4-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.4 + cabal configure -w ghc-8.10.4 - 8_10_4-check: | cd example.org cabal check @@ -591,7 +597,7 @@ tasks: cabal haddock all - 8_10_5-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.5 + cabal configure -w ghc-8.10.5 - 8_10_5-check: | cd example.org cabal check @@ -610,7 +616,7 @@ tasks: cabal haddock all - 8_10_6-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.6 + cabal configure -w ghc-8.10.6 - 8_10_6-check: | cd example.org cabal check @@ -629,7 +635,7 @@ tasks: cabal haddock all - 8_10_7-prepare: | cd example.org - cabal configure -w /opt/ghc/bin/ghc-8.10.7 + cabal configure -w ghc-8.10.7 - 8_10_7-check: | cd example.org cabal check diff --git a/src/HaskellCI/Sourcehut.hs b/src/HaskellCI/Sourcehut.hs index 2f7f7f18..4854ce63 100644 --- a/src/HaskellCI/Sourcehut.hs +++ b/src/HaskellCI/Sourcehut.hs @@ -118,18 +118,36 @@ makeSourcehut' config@Config {..} source prj jobs@JobVersions {..} = mkManifest :: Set CompilerVersion -> Either HsCiError SourcehutManifest mkManifest compilers = do prepare <- fmap (SourcehutTask "all-prepare") $ runSh $ do - sh "export PATH=$PATH:/opt/cabal/bin" - tell_env "PATH" "$PATH:/opt/cabal/bin" + when (cfgGhcupCabal || any isGHCUP compilers) $ do + installGhcup + sh "export PATH=$PATH:$HOME/.ghcup/bin" + tell_env "PATH" "$PATH:$HOME/.ghcup/bin" + if cfgGhcupCabal then installGhcupCabal else do + sh "export PATH=$PATH:/opt/cabal/bin" + tell_env "PATH" "$PATH:/opt/cabal/bin" + for_ (S.filter isGHCUP compilers) $ \compiler -> do + sh $ "\"$HOME/.ghcup/bin/ghcup\" install ghc \"" ++ dispGhcVersion compiler ++ "\"" + unless (all isGHCUP compilers) $ do + sh "export PATH=$PATH:/opt/ghc/bin" + tell_env "PATH" "$PATH:/opt/ghc/bin" sh "cabal update" tasks <- concat <$> traverse mkTasksForGhc (S.toList compilers) + let aptCompilers = S.filter (not . isGHCUP) compilers + aptCabal = + [ "cabal-install-" ++ dispCabalVersion cfgCabalInstallVersion + | not cfgGhcupCabal ] return SourcehutManifest { srhtManifestImage = cfgUbuntu , srhtManifestPackages = + "gcc" : + -- if all GHCs are installed by ghcup, gmp won't be pulled in + -- by ghc, so we install it explicitly + "libgmp-dev" : toList cfgApt ++ - ( "gcc" : "cabal-install-3.4" : - (dispGhcVersion <$> S.toList compilers)) - , srhtManifestRepositories = M.singleton - "hvr-ghc" + aptCabal ++ + (dispGhcVersion <$> S.toList aptCompilers) + , srhtManifestRepositories = if S.null aptCompilers && cfgGhcupCabal + then M.empty else M.singleton "hvr-ghc" ("http://ppa.launchpad.net/hvr/ghc/ubuntu " ++ C.prettyShow cfgUbuntu ++ " main ff3aeacef6f88286") , srhtManifestArtifacts = [] , srhtManifestSources = [source] @@ -145,7 +163,7 @@ makeSourcehut' config@Config {..} source prj jobs@JobVersions {..} = mkTasksForGhc :: CompilerVersion -> Either HsCiError [SourcehutTask] mkTasksForGhc job = sequence $ buildList $ do sourcehutRun "prepare" job clonePath $ - sh $ "cabal configure -w /opt/ghc/bin/" ++ dispGhcVersion job + sh $ "cabal configure -w " ++ dispGhcVersion job sourcehutRun "check" job clonePath $ sh "cabal check" when cfgInstallDeps $ sourcehutRun "dependencies" job clonePath $ do @@ -158,6 +176,21 @@ makeSourcehut' config@Config {..} source prj jobs@JobVersions {..} = when (hasLibrary && not (equivVersionRanges C.noVersion cfgHaddock)) $ sourcehutRun "haddock" job clonePath $ sh "cabal haddock all" + installGhcup :: ShM () + installGhcup = do + let ghcupVer = C.prettyShow cfgGhcupVersion + sh $ "mkdir -p \"$HOME/.ghcup/bin\"" + sh $ "curl -sL https://downloads.haskell.org/ghcup/" ++ ghcupVer ++ "/x86_64-linux-ghcup-" ++ ghcupVer ++ " > \"$HOME/.ghcup/bin/ghcup\"" + sh $ "chmod a+x \"$HOME/.ghcup/bin/ghcup\"" + + installGhcupCabal :: ShM () + installGhcupCabal = + sh $ "\"$HOME/.ghcup/bin/ghcup\" install cabal " ++ dispCabalVersion cfgCabalInstallVersion + + -- job to be setup with ghcup + isGHCUP :: CompilerVersion -> Bool + isGHCUP v = compilerWithinRange v (RangeGHC /\ Range cfgGhcupJobs) + removeSuffix :: String -> String -> String removeSuffix suffix orig = fromMaybe orig $ stripSuffix suffix orig