Skip to content

Commit 67115f5

Browse files
Implement --matrix-extra for more matrix dimensions
Sometimes you need to test your project along more dimensions that 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 maintains that need such a strategy to manually adjust the matrix after every (re)generation of the CI script/spec. Better support for this scenario in haskell-ci 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 a4ea1ed commit 67115f5

File tree

3 files changed

+54
-11
lines changed

3 files changed

+54
-11
lines changed

src/HaskellCI/Config.hs

Lines changed: 26 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -76,6 +76,7 @@ data Config = Config
7676
, cfgPostgres :: !Bool
7777
, cfgGoogleChrome :: !Bool
7878
, cfgEnv :: M.Map Version String
79+
, cfgMatrixExtra :: M.Map String (S.Set String)
7980
, cfgAllowFailures :: !VersionRange
8081
, cfgLastInSeries :: !Bool
8182
, cfgOsx :: S.Set Version
@@ -133,6 +134,7 @@ emptyConfig = Config
133134
, cfgPostgres = False
134135
, cfgGoogleChrome = False
135136
, cfgEnv = M.empty
137+
, cfgMatrixExtra = M.empty
136138
, cfgAllowFailures = noVersion
137139
, cfgLastInSeries = False
138140
, cfgOsx = S.empty
@@ -218,6 +220,8 @@ configGrammar = Config
218220
^^^ help "Add google-chrome service"
219221
<*> C.monoidalFieldAla "env" Env (field @"cfgEnv")
220222
^^^ metahelp "ENV" "Environment variables per job (e.g. `8.0.2:HADDOCK=false`)"
223+
<*> C.monoidalFieldAla "matrix-extra" MatrixExtra (field @"cfgMatrixExtra")
224+
^^^ metahelp "MATRIX" "Extra matrix dimensions (e.g. `libfoo:2.6,3.0,git`)"
221225
<*> C.optionalFieldDefAla "allow-failures" Range (field @"cfgAllowFailures") noVersion
222226
^^^ metahelp "JOB" "Allow failures of particular GHC version"
223227
<*> C.booleanFieldDef "last-in-series" (field @"cfgLastInSeries") False
@@ -290,6 +294,28 @@ instance C.Pretty Env where
290294
pretty (Env m) = PP.fsep . PP.punctuate PP.comma . map p . M.toList $ m where
291295
p (v, s) = C.pretty v PP.<> PP.colon PP.<> PP.text s
292296

297+
298+
-------------------------------------------------------------------------------
299+
-- MatrixExtra
300+
-------------------------------------------------------------------------------
301+
302+
newtype MatrixExtra = MatrixExtra (M.Map String (S.Set String))
303+
deriving anyclass (C.Newtype (M.Map String (S.Set String)))
304+
305+
instance C.Parsec MatrixExtra where
306+
parsec = MatrixExtra . M.fromList . toList <$> C.sepByNonEmpty p (C.char ';')
307+
where
308+
p = do
309+
k <- C.munch1 (/= ':')
310+
_ <- C.char ':'
311+
v <- foldMap S.singleton <$> C.sepByNonEmpty (C.munch1 (`notElem` [',', ';'])) (C.char ',')
312+
pure (k, v)
313+
314+
instance C.Pretty MatrixExtra where
315+
pretty (MatrixExtra m) = PP.fsep . PP.punctuate PP.semi . map p . M.toList $ m where
316+
p (k, v) = PP.text k PP.<> PP.colon PP.<> PP.fsep (PP.punctuate PP.comma (map PP.text (toList v)))
317+
318+
293319
-------------------------------------------------------------------------------
294320
-- From Cabal
295321
-------------------------------------------------------------------------------

src/HaskellCI/GitHub.hs

Lines changed: 25 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -435,15 +435,7 @@ makeGitHub _argv config@Config {..} gitconfig prj jobs@JobVersions {..} = do
435435
, ghjContinueOnError = Just "${{ matrix.allow-failure }}"
436436
, ghjServices = mconcat
437437
[ Map.singleton "postgres" postgresService | cfgPostgres ]
438-
, ghjMatrix =
439-
[ GitHubMatrixEntry
440-
{ ghmeGhcVersion = v
441-
, ghmeAllowFailure =
442-
previewGHC cfgHeadHackage compiler
443-
|| maybeGHC False (`C.withinRange` cfgAllowFailures) compiler
444-
}
445-
| compiler@(GHC v) <- reverse $ toList versions
446-
]
438+
, ghjMatrix = matrix
447439
})
448440
unless (null cfgIrcChannels) $
449441
ircJob mainJobName projectName config gitconfig
@@ -453,6 +445,30 @@ makeGitHub _argv config@Config {..} gitconfig prj jobs@JobVersions {..} = do
453445

454446
Auxiliary {..} = auxiliary config prj jobs
455447

448+
-- extra matrix fields
449+
matrixExtra :: [[(String, String)]]
450+
matrixExtra =
451+
sequence
452+
$ (\(k, vs) -> fmap (\v -> (k, v)) (toList vs))
453+
<$> Map.toList cfgMatrixExtra
454+
455+
mkMatrixEntries :: [(String, String)] -> [GitHubMatrixEntry]
456+
mkMatrixEntries extra =
457+
[ GitHubMatrixEntry
458+
{ ghmeGhcVersion = v
459+
, ghmeAllowFailure =
460+
previewGHC cfgHeadHackage compiler
461+
|| maybeGHC False (`C.withinRange` cfgAllowFailures) compiler
462+
, ghmeMatrixExtra = extra
463+
}
464+
| compiler@(GHC v) <- reverse $ toList versions
465+
]
466+
467+
matrix :: [GitHubMatrixEntry]
468+
matrix = case matrixExtra of
469+
[] -> mkMatrixEntries []
470+
xs -> xs >>= mkMatrixEntries
471+
456472
-- step primitives
457473
githubRun' :: String -> Map.Map String String -> ShM () -> ListBuilder (Either ShError GitHubStep) ()
458474
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
@@ -42,6 +42,7 @@ data GitHubJob = GitHubJob
4242
data GitHubMatrixEntry = GitHubMatrixEntry
4343
{ ghmeGhcVersion :: Version
4444
, ghmeAllowFailure :: Bool
45+
, ghmeMatrixExtra :: [(String, String)]
4546
}
4647
deriving (Show)
4748

@@ -122,10 +123,10 @@ instance ToYaml GitHubJob where
122123
item $ "steps" ~> ylistFilt [] (map toYaml $ filter notEmptyStep ghjSteps)
123124

124125
instance ToYaml GitHubMatrixEntry where
125-
toYaml GitHubMatrixEntry {..} = ykeyValuesFilt []
126+
toYaml GitHubMatrixEntry {..} = ykeyValuesFilt [] $
126127
[ "ghc" ~> fromString (prettyShow ghmeGhcVersion)
127128
, "allow-failure" ~> toYaml ghmeAllowFailure
128-
]
129+
] ++ fmap (\(k, v) -> k ~> fromString v) ghmeMatrixExtra
129130

130131
instance ToYaml GitHubStep where
131132
toYaml GitHubStep {..} = ykeyValuesFilt [] $

0 commit comments

Comments
 (0)