Skip to content
Snippets Groups Projects
Commit 5807fa21 authored by Ben Gamari's avatar Ben Gamari :turtle:
Browse files

ci: Add support for providing additional tested packages on command-line

parent 4aa3f955
No related branches found
No related tags found
No related merge requests found
......@@ -60,6 +60,7 @@ data Config = Config { configPatchDir :: FilePath
, configOnlyPackages :: Maybe (S.Set Cabal.PackageName)
, configConcurrency :: Int
, configExtraCabalFragments :: [FilePath]
, configExtraPackages :: [(Cabal.PackageName, Version)]
, configExpectedBrokenPkgs :: BrokenPackages
}
......@@ -79,6 +80,7 @@ config =
<*> onlyPackages
<*> concurrency
<*> extraCabalFragments
<*> extraPackages
<*> expectedBrokenPkgs
where
patchDir = option str (short 'p' <> long "patches" <> help "patch directory" <> value "./patches")
......@@ -90,12 +92,26 @@ config =
<|> pure Nothing
concurrency = option auto (short 'j' <> long "concurrency" <> value 1 <> help "number of concurrent builds")
extraCabalFragments = many $ option str (long "extra-cabal-fragment" <> help "path of extra configuration to include in cabal project files")
extraPackages = many $ option pkgVer (short 'P' <> long "extra-package" <> help "other, un-patched packages to test")
expectedBrokenPkgs =
fmap (BrokenPackages . S.fromList) $ many
$ option
(fmap toPkgName pkgName)
(short 'b' <> long "expect-broken" <> metavar "PKGNAME" <> help "expect the given package to fail to build")
pkgVer :: ReadM (Cabal.PackageName, Version)
pkgVer = str >>= parse . T.pack
where
parse s
| [name, ver] <- T.splitOn "==" s
, Just ver' <- simpleParse $ T.unpack ver
= pure (Cabal.mkPackageName $ T.unpack name, ver')
| otherwise
= fail $ unlines
[ "Invalid extra package specified:"
, "expected to be in form of PKG_NAME==VERSION"
]
pkgName :: ReadM Cabal.PackageName
pkgName = str >>= maybe (fail "invalid package name") pure . simpleParse
......@@ -103,6 +119,7 @@ testPatches :: Config -> IO ()
testPatches cfg = do
setup cfg
packages <- findPatchedPackages (configPatchDir cfg)
packages <- return (packages ++ configExtraPackages cfg)
let packages' :: S.Set (Cabal.PackageName, Version)
packages'
| Just only <- configOnlyPackages cfg
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment