Skip to content

Commit 0d590fd

Browse files
Implement --matrix-extra for more matrix dimensions
Sometimes you need to test your project along more dimensions than just GHC version. This is particularly important for programs/libraries that use FFI to bind to libraries - they might need to be tested against a range of library versions. In general, you want to test all the combinations of GHC versions and other properties, i.e. the cartesian product. It is burdensome for maintainers that need such a strategy to manually adjust the matrix after every (re)generation of the CI script/spec. Better tool support for this scenario is warranted. This commit implements a new --matrix-extra option, which adds additional matrix dimensions. The option value format is: --matrix-extra libfoo:2.6,3.0;libbar:0.1,0.2 haskell-ci adds all the combinations of GHC version and the --matrix-extra fields to the matrix. Corresponding build/test steps can be introduced via --github-patches (or --travis-patches). This commit implements this feature for GitHub actions only. It can be implemented for Travis in a subsequent commit, if desired.
1 parent a5bacf0 commit 0d590fd

File tree

3 files changed

+57
-15
lines changed

3 files changed

+57
-15
lines changed

src/HaskellCI/Config.hs

Lines changed: 26 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -83,6 +83,7 @@ data Config = Config
8383
, cfgPostgres :: !Bool
8484
, cfgGoogleChrome :: !Bool
8585
, cfgEnv :: M.Map Version String
86+
, cfgMatrixExtra :: M.Map String (S.Set String)
8687
, cfgAllowFailures :: !VersionRange
8788
, cfgLastInSeries :: !Bool
8889
, cfgLinuxJobs :: !VersionRange
@@ -132,7 +133,7 @@ configGrammar
132133
, c (Identity Version)
133134
, c (Identity Natural)
134135
, c (Identity Components)
135-
, c Env, c Folds, c CopyFields, c HeadVersion
136+
, c Env, c MatrixExtra, c Folds, c CopyFields, c HeadVersion
136137
, c (C.List C.FSep (Identity Installed) Installed)
137138
, Applicative (g DoctestConfig)
138139
, Applicative (g DocspecConfig)
@@ -215,6 +216,8 @@ configGrammar = Config
215216
^^^ help "Add google-chrome service"
216217
<*> C.monoidalFieldAla "env" Env (field @"cfgEnv")
217218
^^^ metahelp "ENV" "Environment variables per job (e.g. `8.0.2:HADDOCK=false`)"
219+
<*> C.monoidalFieldAla "matrix-extra" MatrixExtra (field @"cfgMatrixExtra")
220+
^^^ metahelp "MATRIX" "Extra matrix dimensions (e.g. `libfoo:2.6,3.0,git`)"
218221
<*> C.optionalFieldDefAla "allow-failures" Range (field @"cfgAllowFailures") noVersion
219222
^^^ metahelp "JOB" "Allow failures of particular GHC version"
220223
<*> C.booleanFieldDef "last-in-series" (field @"cfgLastInSeries") False
@@ -305,6 +308,28 @@ instance C.Pretty Env where
305308
pretty (Env m) = PP.fsep . PP.punctuate PP.comma . map p . M.toList $ m where
306309
p (v, s) = C.pretty v PP.<> PP.colon PP.<> PP.text s
307310

311+
312+
-------------------------------------------------------------------------------
313+
-- MatrixExtra
314+
-------------------------------------------------------------------------------
315+
316+
newtype MatrixExtra = MatrixExtra (M.Map String (S.Set String))
317+
deriving anyclass (C.Newtype (M.Map String (S.Set String)))
318+
319+
instance C.Parsec MatrixExtra where
320+
parsec = MatrixExtra . M.fromList . toList <$> C.sepByNonEmpty p (C.char ';')
321+
where
322+
p = do
323+
k <- C.munch1 (/= ':')
324+
_ <- C.char ':'
325+
v <- foldMap S.singleton <$> C.sepByNonEmpty (C.munch1 (`notElem` [',', ';'])) (C.char ',')
326+
pure (k, v)
327+
328+
instance C.Pretty MatrixExtra where
329+
pretty (MatrixExtra m) = PP.fsep . PP.punctuate PP.semi . map p . M.toList $ m where
330+
p (k, v) = PP.text k PP.<> PP.colon PP.<> PP.fsep (PP.punctuate PP.comma (map PP.text (toList v)))
331+
332+
308333
-------------------------------------------------------------------------------
309334
-- From Cabal
310335
-------------------------------------------------------------------------------

src/HaskellCI/GitHub.hs

Lines changed: 28 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -618,18 +618,7 @@ makeGitHub _argv config@Config {..} gitconfig prj jobs@JobVersions {..} = do
618618
, ghjServices = mconcat
619619
[ Map.singleton "postgres" postgresService | cfgPostgres ]
620620
, ghjTimeout = max 10 cfgTimeoutMinutes
621-
, ghjMatrix =
622-
[ GitHubMatrixEntry
623-
{ ghmeCompiler = translateCompilerVersion $ compiler
624-
, ghmeAllowFailure =
625-
previewGHC cfgHeadHackage compiler
626-
|| maybeGHC False (`C.withinRange` cfgAllowFailures) compiler
627-
, ghmeSetupMethod = if isGHCUP compiler then GHCUP else HVRPPA
628-
}
629-
| compiler <- reverse $ toList linuxVersions
630-
, compiler /= GHCHead -- TODO: Make this work
631-
-- https://github.com/haskell-CI/haskell-ci/issues/458
632-
]
621+
, ghjMatrix = matrix
633622
})
634623
unless (null cfgIrcChannels) $
635624
ircJob actionName mainJobName projectName config gitconfig
@@ -678,6 +667,33 @@ makeGitHub _argv config@Config {..} gitconfig prj jobs@JobVersions {..} = do
678667
isGHCUP :: CompilerVersion -> Bool
679668
isGHCUP v = compilerWithinRange v (RangeGHC /\ Range cfgGhcupJobs)
680669

670+
-- extra matrix fields
671+
matrixExtra :: [[(String, String)]]
672+
matrixExtra =
673+
sequence
674+
$ (\(k, vs) -> fmap (\v -> (k, v)) (toList vs))
675+
<$> Map.toList cfgMatrixExtra
676+
677+
mkMatrixEntries :: [(String, String)] -> [GitHubMatrixEntry]
678+
mkMatrixEntries extra =
679+
[ GitHubMatrixEntry
680+
{ ghmeCompiler = translateCompilerVersion $ compiler
681+
, ghmeAllowFailure =
682+
previewGHC cfgHeadHackage compiler
683+
|| maybeGHC False (`C.withinRange` cfgAllowFailures) compiler
684+
, ghmeSetupMethod = if isGHCUP compiler then GHCUP else HVRPPA
685+
, ghmeMatrixExtra = extra
686+
}
687+
| compiler <- reverse $ toList linuxVersions
688+
, compiler /= GHCHead -- TODO: Make this work
689+
-- https://github.com/haskell-CI/haskell-ci/issues/458
690+
]
691+
692+
matrix :: [GitHubMatrixEntry]
693+
matrix = case matrixExtra of
694+
[] -> mkMatrixEntries []
695+
xs -> xs >>= mkMatrixEntries
696+
681697
-- step primitives
682698
githubRun' :: String -> Map.Map String String -> ShM () -> ListBuilder (Either HsCiError GitHubStep) ()
683699
githubRun' name env shm = item $ do

src/HaskellCI/GitHub/Yaml.hs

Lines changed: 3 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -48,6 +48,7 @@ data SetupMethod = HVRPPA | GHCUP
4848
data GitHubMatrixEntry = GitHubMatrixEntry
4949
{ ghmeCompiler :: CompilerVersion
5050
, ghmeAllowFailure :: Bool
51+
, ghmeMatrixExtra :: [(String, String)]
5152
, ghmeSetupMethod :: SetupMethod
5253
}
5354
deriving (Show)
@@ -134,13 +135,13 @@ instance ToYaml SetupMethod where
134135
toYaml GHCUP = "ghcup"
135136

136137
instance ToYaml GitHubMatrixEntry where
137-
toYaml GitHubMatrixEntry {..} = ykeyValuesFilt []
138+
toYaml GitHubMatrixEntry {..} = ykeyValuesFilt [] $
138139
[ "compiler" ~> fromString (dispGhcVersion ghmeCompiler)
139140
, "compilerKind" ~> fromString (compilerKind ghmeCompiler)
140141
, "compilerVersion" ~> fromString (compilerVersion ghmeCompiler)
141142
, "setup-method" ~> toYaml ghmeSetupMethod
142143
, "allow-failure" ~> toYaml ghmeAllowFailure
143-
]
144+
] ++ fmap (\(k, v) -> k ~> fromString v) ghmeMatrixExtra
144145

145146
instance ToYaml GitHubStep where
146147
toYaml GitHubStep {..} = ykeyValuesFilt [] $

0 commit comments

Comments
 (0)