[Git][ghc/ghc][wip/test-primops] 4 commits: gen_ci: Rules rework
Matthew Pickering (@mpickering)
gitlab at gitlab.haskell.org
Sun Aug 6 09:05:31 UTC 2023
Matthew Pickering pushed to branch wip/test-primops at Glasgow Haskell Compiler / GHC
Commits:
29781930 by Matthew Pickering at 2023-08-06T10:04:55+01:00
gen_ci: Rules rework
In particular we now distinguish between whether we are dealing with a
Nightly/Release pipeline (which labels don't matter for) and a validate
pipeline where labels do matter.
The overall goal here is to allow a disjunction of labels for validate
pipelines, for example,
> Run a job if we have the full-ci label or test-primops label
Therefore the "ValidateOnly" rules are treated as a set of disjunctions
rather than conjunctions like before.
What this means in particular is that if we want to ONLY run a job if a
label is set, for example, "FreeBSD" label then we have to override the
whole label set.
Fixes #23772
- - - - -
7c3546ee by Matthew Pickering at 2023-08-06T10:05:04+01:00
Add test-primops label support
The test-primops CI job requires some additional builds in the
validation pipeline, so we make sure to enable these jobs when
test-primops label is set.
- - - - -
b6a4ba2a by Matthew Pickering at 2023-08-06T10:05:04+01:00
ci: set -e for lint-ci-config scripts
- - - - -
7b28b11d by Matthew Pickering at 2023-08-06T10:05:04+01:00
ci: Fix job metadata generation
- - - - -
4 changed files:
- .gitlab/generate-ci/gen_ci.hs
- .gitlab/generate-ci/generate-job-metadata
- .gitlab/generate-ci/generate-jobs
- .gitlab/jobs.yaml
Changes:
=====================================
.gitlab/generate-ci/gen_ci.hs
=====================================
@@ -11,7 +11,6 @@ import Data.Map (Map)
import Data.Maybe
import qualified Data.ByteString.Lazy as B
import qualified Data.ByteString.Lazy.Char8 as B
-import Data.Set (Set)
import qualified Data.Set as S
import System.Environment
import Data.List
@@ -503,21 +502,34 @@ instance ToJSON ArtifactsWhen where
-----------------------------------------------------------------------------
-- Data structure which records the condition when a job is run.
-data OnOffRules = OnOffRules { rule_set :: Set Rule -- ^ The set of enabled rules
+data OnOffRules = OnOffRules { rule_set :: Rule -- ^ The enabled rules
, when :: ManualFlag -- ^ The additional condition about when to run this job.
}
--- The initial set of rules where all rules are disabled and the job is always run.
+-- The initial set of rules, which assumes a Validate pipeline which is run with FullCI.
emptyRules :: OnOffRules
-emptyRules = OnOffRules S.empty OnSuccess
+emptyRules = OnOffRules (ValidateOnly (S.singleton FullCI)) OnSuccess
-- When to run the job
data ManualFlag = Manual -- ^ Only run the job when explicitly triggered by a user
| OnSuccess -- ^ Always run it, if the rules pass (the default)
deriving Eq
-enableRule :: Rule -> OnOffRules -> OnOffRules
-enableRule r (OnOffRules o m) = OnOffRules (S.insert r o) m
+setRule :: Rule -> OnOffRules -> OnOffRules
+setRule r (OnOffRules _ m) = OnOffRules r m
+
+enableValidateRule :: ValidateRule -> OnOffRules -> OnOffRules
+enableValidateRule r = modifyValidateRules (S.insert r)
+
+onlyValidateRule :: ValidateRule -> OnOffRules -> OnOffRules
+onlyValidateRule r = modifyValidateRules (const (S.singleton r))
+
+removeValidateRule :: ValidateRule -> OnOffRules -> OnOffRules
+removeValidateRule r = modifyValidateRules (S.delete r)
+
+modifyValidateRules :: (S.Set ValidateRule -> S.Set ValidateRule) -> OnOffRules -> OnOffRules
+modifyValidateRules f (OnOffRules (ValidateOnly rs) m) = OnOffRules (ValidateOnly (f rs)) m
+modifyValidateRules _ r = error $ "Applying validate rule to nightly/release job:" ++ show (rule_set r)
manualRule :: OnOffRules -> OnOffRules
manualRule rules = rules { when = Manual }
@@ -526,10 +538,19 @@ manualRule rules = rules { when = Manual }
-- For example, even if you don't explicitly disable a rule it will end up in the
-- rule list with the OFF state.
enumRules :: OnOffRules -> [OnOffRule]
-enumRules o = map lkup rulesList
+enumRules (OnOffRules r _) = rulesList
where
- enabled_rules = rule_set o
- lkup r = OnOffRule (if S.member r enabled_rules then On else Off) r
+ rulesList = case r of
+ ValidateOnly rs -> [OnOffRule On (ValidateOnly rs)
+ , OnOffRule Off ReleaseOnly
+ , OnOffRule Off Nightly ]
+ Nightly -> [ OnOffRule Off (ValidateOnly S.empty)
+ , OnOffRule Off ReleaseOnly
+ , OnOffRule On Nightly ]
+ ReleaseOnly -> [ OnOffRule Off (ValidateOnly S.empty)
+ , OnOffRule On ReleaseOnly
+ , OnOffRule Off Nightly ]
+
data OnOffRule = OnOffRule OnOff Rule
@@ -551,21 +572,30 @@ instance ToJSON OnOffRules where
where
one_rule (OnOffRule onoff r) = ruleString onoff r
- parens s = "(" ++ s ++ ")"
- and_all rs = intercalate " && " (map parens rs)
+
+
+parens :: [Char] -> [Char]
+parens s = "(" ++ s ++ ")"
+and_all :: [[Char]] -> [Char]
+and_all rs = intercalate " && " (map parens rs)
+or_all :: [[Char]] -> [Char]
+or_all rs = intercalate " || " (map parens rs)
-- | A Rule corresponds to some condition which must be satisifed in order to
-- run the job.
-data Rule = FastCI -- ^ Run this job on all validate pipelines, all pipelines are enabled
- -- by the "full-ci" label.
- | ReleaseOnly -- ^ Only run this job in a release pipeline
+data Rule = ReleaseOnly -- ^ Only run this job in a release pipeline
| Nightly -- ^ Only run this job in the nightly pipeline
- | LLVMBackend -- ^ Only run this job when the "LLVM backend" label is present
- | FreeBSDLabel -- ^ Only run this job when the "FreeBSD" label is set.
- | NonmovingGc -- ^ Only run this job when the "non-moving GC" label is set.
- | IpeData -- ^ Only run this job when the "IPE" label is set
- | Disable -- ^ Don't run this job.
- deriving (Bounded, Enum, Ord, Eq)
+ | ValidateOnly (S.Set ValidateRule) -- ^ Only run this job in a validate pipeline, when any of these rules are enabled.
+ deriving (Show, Ord, Eq)
+
+data ValidateRule =
+ FullCI -- ^ Run this job when the "full-ci" label is present.
+ | LLVMBackend -- ^ Run this job when the "LLVM backend" label is present
+ | FreeBSDLabel -- ^ Run this job when the "FreeBSD" label is set.
+ | NonmovingGc -- ^ Run this job when the "non-moving GC" label is set.
+ | IpeData -- ^ Run this job when the "IPE" label is set
+ | TestPrimops -- ^ Run this job when "test-primops" label is set
+ deriving (Show, Enum, Bounded, Ord, Eq)
-- A constant evaluating to True because gitlab doesn't support "true" in the
-- expression language.
@@ -573,31 +603,31 @@ true :: String
true = "\"true\" == \"true\""
-- A constant evaluating to False because gitlab doesn't support "true" in the
-- expression language.
-false :: String
-false = "\"disabled\" != \"disabled\""
+_false :: String
+_false = "\"disabled\" != \"disabled\""
-- Convert the state of the rule into a string that gitlab understand.
ruleString :: OnOff -> Rule -> String
-ruleString On FastCI = true
-ruleString Off FastCI = "($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/)"
-ruleString On LLVMBackend = "$CI_MERGE_REQUEST_LABELS =~ /.*LLVM backend.*/"
-ruleString Off LLVMBackend = true
-ruleString On FreeBSDLabel = "$CI_MERGE_REQUEST_LABELS =~ /.*FreeBSD.*/"
-ruleString Off FreeBSDLabel = true
-ruleString On NonmovingGc = "$CI_MERGE_REQUEST_LABELS =~ /.*non-moving GC.*/"
-ruleString Off NonmovingGc = true
+ruleString On (ValidateOnly vs) =
+ case S.toList vs of
+ [] -> true
+ conds -> or_all (map validateRuleString conds)
+ruleString Off (ValidateOnly {}) = true
ruleString On ReleaseOnly = "$RELEASE_JOB == \"yes\""
ruleString Off ReleaseOnly = "$RELEASE_JOB != \"yes\""
ruleString On Nightly = "$NIGHTLY"
ruleString Off Nightly = "$NIGHTLY == null"
-ruleString On IpeData = "$CI_MERGE_REQUEST_LABELS =~ /.*IPE.*/"
-ruleString Off IpeData = true
-ruleString On Disable = false
-ruleString Off Disable = true
--- Enumeration of all the rules
-rulesList :: [Rule]
-rulesList = [minBound .. maxBound]
+labelString :: String -> String
+labelString s = "$CI_MERGE_REQUEST_LABELS =~ /.*" ++ s ++ ".*/"
+
+validateRuleString :: ValidateRule -> String
+validateRuleString FullCI = or_all ([labelString "full-ci", labelString "marge_bot_batch_merge_job"])
+validateRuleString LLVMBackend = labelString "LLVM backend"
+validateRuleString FreeBSDLabel = labelString "FreeBSD"
+validateRuleString NonmovingGc = labelString "non-moving GC"
+validateRuleString IpeData = labelString "IPE"
+validateRuleString TestPrimops = labelString "test-primops"
-- | A 'Job' is the description of a single job in a gitlab pipeline. The
-- job contains all the information about how to do the build but can be further
@@ -750,8 +780,20 @@ modifyNightlyJobs f jg = jg { n = fmap f <$> n jg }
-- Generic helpers
-addJobRule :: Rule -> Job -> Job
-addJobRule r j = j { jobRules = enableRule r (jobRules j) }
+setJobRule :: Rule -> Job -> Job
+setJobRule r j = j { jobRules = setRule r (jobRules j) }
+
+addValidateJobRule :: ValidateRule -> Job -> Job
+addValidateJobRule r = modifyValidateJobRule (enableValidateRule r)
+
+onlyValidateJobRule :: ValidateRule -> Job -> Job
+onlyValidateJobRule r = modifyValidateJobRule (onlyValidateRule r)
+
+removeValidateJobRule :: ValidateRule -> Job -> Job
+removeValidateJobRule r = modifyValidateJobRule (removeValidateRule r)
+
+modifyValidateJobRule :: (OnOffRules -> OnOffRules) -> Job -> Job
+modifyValidateJobRule f j = j { jobRules = f (jobRules j) }
addVariable :: String -> String -> Job -> Job
addVariable k v j = j { jobVariables = mminsertWith (++) k [v] (jobVariables j) }
@@ -771,10 +813,10 @@ validate = job
-- Nightly and release apply the FastCI configuration to all jobs so that they all run in
-- the pipeline (not conditional on the full-ci label)
nightlyRule :: Job -> Job
-nightlyRule = addJobRule FastCI . addJobRule Nightly
+nightlyRule = setJobRule Nightly
releaseRule :: Job -> Job
-releaseRule = addJobRule FastCI . addJobRule ReleaseOnly
+releaseRule = setJobRule ReleaseOnly
-- | Make a normal nightly CI job
nightly :: Arch -> Opsys -> BuildConfig -> NamedJob Job
@@ -817,7 +859,7 @@ useHashUnitIds = addVariable "HADRIAN_ARGS" "--hash-unit-ids"
-- | Mark the validate job to run in fast-ci mode
-- This is default way, to enable all jobs you have to apply the `full-ci` label.
fastCI :: JobGroup Job -> JobGroup Job
-fastCI = modifyValidateJobs (addJobRule FastCI)
+fastCI = modifyValidateJobs (removeValidateJobRule FullCI)
-- | Mark a group of jobs as allowed to fail.
allowFailureGroup :: JobGroup Job -> JobGroup Job
@@ -825,8 +867,12 @@ allowFailureGroup = modifyJobs allowFailure
-- | Add a 'Rule' to just the validate job, for example, only run a job if a certain
-- label is set.
-addValidateRule :: Rule -> JobGroup Job -> JobGroup Job
-addValidateRule t = modifyValidateJobs (addJobRule t)
+addValidateRule :: ValidateRule -> JobGroup Job -> JobGroup Job
+addValidateRule t = modifyValidateJobs (addValidateJobRule t)
+
+-- | Only run a validate job if a certain rule is enabled
+onlyRule :: ValidateRule -> JobGroup Job -> JobGroup Job
+onlyRule t = modifyValidateJobs (onlyValidateJobRule t)
-- | Don't run the validate job, normally used to alleviate CI load by marking
-- jobs which are unlikely to fail (ie different linux distros)
@@ -891,14 +937,12 @@ flattenNamedJob (NamedJob n i) = (n, i)
-- | Specification for all the jobs we want to build.
jobs :: Map String Job
-jobs = Map.fromList $ concatMap (filter is_enabled_job . flattenJobGroup) job_groups
- where
- is_enabled_job (_, Job {jobRules = OnOffRules {..}}) = not $ Disable `S.member` rule_set
+jobs = Map.fromList $ concatMap (flattenJobGroup) job_groups
job_groups :: [JobGroup Job]
job_groups =
[ disableValidate (standardBuilds Amd64 (Linux Debian10))
- , standardBuildsWithConfig Amd64 (Linux Debian10) dwarf
+ , addValidateRule TestPrimops (standardBuildsWithConfig Amd64 (Linux Debian10) dwarf)
, validateBuilds Amd64 (Linux Debian10) nativeInt
, validateBuilds Amd64 (Linux Debian10) unreg
, fastCI (validateBuilds Amd64 (Linux Debian10) debug)
@@ -908,7 +952,7 @@ job_groups =
, -- Nightly allowed to fail: #22343
modifyNightlyJobs allowFailure
(modifyValidateJobs manual (validateBuilds Amd64 (Linux Debian10) noTntc))
- , addValidateRule LLVMBackend (validateBuilds Amd64 (Linux Debian10) llvm)
+ , onlyRule LLVMBackend (validateBuilds Amd64 (Linux Debian10) llvm)
, disableValidate (standardBuilds Amd64 (Linux Debian11))
-- We still build Deb9 bindists for now due to Ubuntu 18 and Linux Mint 19
-- not being at EOL until April 2023 and they still need tinfo5.
@@ -925,8 +969,8 @@ job_groups =
, disableValidate (standardBuildsWithConfig Amd64 (Linux Fedora33) dwarf)
, fastCI (standardBuildsWithConfig Amd64 Windows vanilla)
, disableValidate (standardBuildsWithConfig Amd64 Windows nativeInt)
- , standardBuilds Amd64 Darwin
- , allowFailureGroup (addValidateRule FreeBSDLabel (validateBuilds Amd64 FreeBSD13 vanilla))
+ , addValidateRule TestPrimops (standardBuilds Amd64 Darwin)
+ , allowFailureGroup (onlyRule FreeBSDLabel (validateBuilds Amd64 FreeBSD13 vanilla))
, fastCI (standardBuilds AArch64 Darwin)
, fastCI (standardBuildsWithConfig AArch64 (Linux Debian10) (splitSectionsBroken vanilla))
, disableValidate (validateBuilds AArch64 (Linux Debian10) llvm)
@@ -946,9 +990,8 @@ job_groups =
make_wasm_jobs wasm_build_config {bignumBackend = Native}
, modifyValidateJobs manual $
make_wasm_jobs wasm_build_config {unregisterised = True}
- , addValidateRule NonmovingGc (standardBuildsWithConfig Amd64 (Linux Debian11) vanilla {validateNonmovingGc = True})
- , modifyNightlyJobs (addJobRule Disable) $
- addValidateRule IpeData (validateBuilds Amd64 (Linux Debian10) zstdIpe)
+ , onlyRule NonmovingGc (standardBuildsWithConfig Amd64 (Linux Debian11) vanilla {validateNonmovingGc = True})
+ , onlyRule IpeData (validateBuilds Amd64 (Linux Debian10) zstdIpe)
]
where
@@ -1018,7 +1061,7 @@ platform_mapping = Map.map go combined_result
, "release-x86_64-linux-deb10-release"
, "release-x86_64-linux-deb11-release"
, "release-x86_64-linux-fedora33-release"
- , "release-x86_64-windows-release+no_split_sections"
+ , "release-x86_64-windows-release"
]
process sel = Map.fromListWith combine [ (uncurry mkPlatform (jobPlatform (jobInfo $ j)), j) | (sel -> Just j) <- job_groups ]
@@ -1057,6 +1100,7 @@ main = do
("metadata":as) -> write_result as platform_mapping
_ -> error "gen_ci.hs <gitlab|metadata> [file.json]"
+write_result :: ToJSON a => [FilePath] -> a -> IO ()
write_result as obj =
(case as of
[] -> B.putStrLn
=====================================
.gitlab/generate-ci/generate-job-metadata
=====================================
@@ -1,5 +1,7 @@
#!/usr/bin/env bash
+set -e
+
out_dir="$(git rev-parse --show-toplevel)/.gitlab"
# Update job metadata for ghcup
=====================================
.gitlab/generate-ci/generate-jobs
=====================================
@@ -1,5 +1,7 @@
#!/usr/bin/env bash
+set -e
+
out_dir="$(git rev-parse --show-toplevel)/.gitlab"
tmp="$(mktemp)"
=====================================
.gitlab/jobs.yaml
=====================================
@@ -37,7 +37,7 @@
],
"rules": [
{
- "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null) && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\")",
+ "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
"when": "on_success"
}
],
@@ -102,7 +102,7 @@
],
"rules": [
{
- "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null) && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\")",
+ "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
"when": "on_success"
}
],
@@ -163,7 +163,7 @@
],
"rules": [
{
- "if": "(($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/)) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null) && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\")",
+ "if": "((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
"when": "on_success"
}
],
@@ -224,7 +224,7 @@
],
"rules": [
{
- "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY) && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\")",
+ "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY)",
"when": "on_success"
}
],
@@ -290,7 +290,7 @@
],
"rules": [
{
- "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY) && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\")",
+ "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY)",
"when": "on_success"
}
],
@@ -352,7 +352,7 @@
],
"rules": [
{
- "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY) && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\")",
+ "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY)",
"when": "on_success"
}
],
@@ -414,7 +414,7 @@
],
"rules": [
{
- "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY) && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\")",
+ "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY)",
"when": "on_success"
}
],
@@ -476,7 +476,7 @@
],
"rules": [
{
- "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY) && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\")",
+ "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY)",
"when": "on_success"
}
],
@@ -545,7 +545,7 @@
],
"rules": [
{
- "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY) && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\")",
+ "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY)",
"when": "on_success"
}
],
@@ -609,7 +609,7 @@
],
"rules": [
{
- "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY) && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\")",
+ "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY)",
"when": "on_success"
}
],
@@ -674,7 +674,7 @@
],
"rules": [
{
- "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY) && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\")",
+ "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY)",
"when": "on_success"
}
],
@@ -739,7 +739,7 @@
],
"rules": [
{
- "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY) && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\")",
+ "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY)",
"when": "on_success"
}
],
@@ -804,7 +804,7 @@
],
"rules": [
{
- "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY) && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\")",
+ "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY)",
"when": "on_success"
}
],
@@ -868,7 +868,7 @@
],
"rules": [
{
- "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY) && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\")",
+ "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY)",
"when": "on_success"
}
],
@@ -932,7 +932,7 @@
],
"rules": [
{
- "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY) && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\")",
+ "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY)",
"when": "on_success"
}
],
@@ -996,7 +996,7 @@
],
"rules": [
{
- "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY) && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\")",
+ "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY)",
"when": "on_success"
}
],
@@ -1059,7 +1059,7 @@
],
"rules": [
{
- "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY) && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\")",
+ "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY)",
"when": "on_success"
}
],
@@ -1121,7 +1121,7 @@
],
"rules": [
{
- "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY) && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\")",
+ "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY)",
"when": "on_success"
}
],
@@ -1183,7 +1183,7 @@
],
"rules": [
{
- "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY) && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\")",
+ "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY)",
"when": "on_success"
}
],
@@ -1246,7 +1246,7 @@
],
"rules": [
{
- "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY) && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\")",
+ "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY)",
"when": "on_success"
}
],
@@ -1308,7 +1308,7 @@
],
"rules": [
{
- "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY) && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\")",
+ "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY)",
"when": "on_success"
}
],
@@ -1370,7 +1370,7 @@
],
"rules": [
{
- "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY) && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\")",
+ "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY)",
"when": "on_success"
}
],
@@ -1432,7 +1432,7 @@
],
"rules": [
{
- "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY) && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\")",
+ "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY)",
"when": "on_success"
}
],
@@ -1494,7 +1494,7 @@
],
"rules": [
{
- "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY) && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\")",
+ "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY)",
"when": "on_success"
}
],
@@ -1521,6 +1521,68 @@
"XZ_OPT": "-9"
}
},
+ "nightly-x86_64-linux-deb10-zstd-validate": {
+ "after_script": [
+ ".gitlab/ci.sh save_cache",
+ ".gitlab/ci.sh save_test_output",
+ ".gitlab/ci.sh clean",
+ "cat ci_timings"
+ ],
+ "allow_failure": false,
+ "artifacts": {
+ "expire_in": "8 weeks",
+ "paths": [
+ "ghc-x86_64-linux-deb10-zstd-validate.tar.xz",
+ "junit.xml",
+ "unexpected-test-output.tar.gz"
+ ],
+ "reports": {
+ "junit": "junit.xml"
+ },
+ "when": "always"
+ },
+ "cache": {
+ "key": "x86_64-linux-deb10-$CACHE_REV",
+ "paths": [
+ "cabal-cache",
+ "toolchain"
+ ]
+ },
+ "dependencies": [],
+ "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb10:$DOCKER_REV",
+ "needs": [
+ {
+ "artifacts": false,
+ "job": "hadrian-ghc-in-ghci"
+ }
+ ],
+ "rules": [
+ {
+ "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY)",
+ "when": "on_success"
+ }
+ ],
+ "script": [
+ "sudo chown ghc:ghc -R .",
+ ".gitlab/ci.sh setup",
+ ".gitlab/ci.sh configure",
+ ".gitlab/ci.sh build_hadrian",
+ ".gitlab/ci.sh test_hadrian"
+ ],
+ "stage": "full-build",
+ "tags": [
+ "x86_64-linux"
+ ],
+ "variables": {
+ "BIGNUM_BACKEND": "gmp",
+ "BIN_DIST_NAME": "ghc-x86_64-linux-deb10-zstd-validate",
+ "BUILD_FLAVOUR": "validate",
+ "CONFIGURE_ARGS": "--enable-ipe-data-compression",
+ "RUNTEST_ARGS": "",
+ "TEST_ENV": "x86_64-linux-deb10-zstd-validate",
+ "XZ_OPT": "-9"
+ }
+ },
"nightly-x86_64-linux-deb11-cross_aarch64-linux-gnu-validate": {
"after_script": [
".gitlab/ci.sh save_cache",
@@ -1558,7 +1620,7 @@
],
"rules": [
{
- "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY) && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\")",
+ "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY)",
"when": "on_success"
}
],
@@ -1622,7 +1684,7 @@
],
"rules": [
{
- "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY) && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\")",
+ "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY)",
"when": "on_success"
}
],
@@ -1687,7 +1749,7 @@
],
"rules": [
{
- "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY) && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\")",
+ "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY)",
"when": "on_success"
}
],
@@ -1749,7 +1811,7 @@
],
"rules": [
{
- "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY) && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\")",
+ "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY)",
"when": "on_success"
}
],
@@ -1811,7 +1873,7 @@
],
"rules": [
{
- "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY) && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\")",
+ "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY)",
"when": "on_success"
}
],
@@ -1873,7 +1935,7 @@
],
"rules": [
{
- "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY) && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\")",
+ "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY)",
"when": "on_success"
}
],
@@ -1937,7 +1999,7 @@
],
"rules": [
{
- "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY) && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\")",
+ "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY)",
"when": "on_success"
}
],
@@ -2002,7 +2064,7 @@
],
"rules": [
{
- "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY) && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\")",
+ "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY)",
"when": "on_success"
}
],
@@ -2066,7 +2128,7 @@
],
"rules": [
{
- "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY) && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\")",
+ "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY)",
"when": "on_success"
}
],
@@ -2129,7 +2191,7 @@
],
"rules": [
{
- "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY) && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\")",
+ "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY)",
"when": "on_success"
}
],
@@ -2191,7 +2253,7 @@
],
"rules": [
{
- "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY) && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\")",
+ "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY)",
"when": "on_success"
}
],
@@ -2249,7 +2311,7 @@
],
"rules": [
{
- "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY) && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\")",
+ "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY)",
"when": "on_success"
}
],
@@ -2311,7 +2373,7 @@
],
"rules": [
{
- "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY) && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\")",
+ "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY)",
"when": "on_success"
}
],
@@ -2377,7 +2439,7 @@
],
"rules": [
{
- "if": "(\"true\" == \"true\") && ($RELEASE_JOB == \"yes\") && ($NIGHTLY == null) && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\")",
+ "if": "(\"true\" == \"true\") && ($RELEASE_JOB == \"yes\") && ($NIGHTLY == null)",
"when": "on_success"
}
],
@@ -2444,7 +2506,7 @@
],
"rules": [
{
- "if": "(\"true\" == \"true\") && ($RELEASE_JOB == \"yes\") && ($NIGHTLY == null) && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\")",
+ "if": "(\"true\" == \"true\") && ($RELEASE_JOB == \"yes\") && ($NIGHTLY == null)",
"when": "on_success"
}
],
@@ -2508,7 +2570,7 @@
],
"rules": [
{
- "if": "(\"true\" == \"true\") && ($RELEASE_JOB == \"yes\") && ($NIGHTLY == null) && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\")",
+ "if": "(\"true\" == \"true\") && ($RELEASE_JOB == \"yes\") && ($NIGHTLY == null)",
"when": "on_success"
}
],
@@ -2572,7 +2634,7 @@
],
"rules": [
{
- "if": "(\"true\" == \"true\") && ($RELEASE_JOB == \"yes\") && ($NIGHTLY == null) && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\")",
+ "if": "(\"true\" == \"true\") && ($RELEASE_JOB == \"yes\") && ($NIGHTLY == null)",
"when": "on_success"
}
],
@@ -2642,7 +2704,7 @@
],
"rules": [
{
- "if": "(\"true\" == \"true\") && ($RELEASE_JOB == \"yes\") && ($NIGHTLY == null) && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\")",
+ "if": "(\"true\" == \"true\") && ($RELEASE_JOB == \"yes\") && ($NIGHTLY == null)",
"when": "on_success"
}
],
@@ -2708,7 +2770,7 @@
],
"rules": [
{
- "if": "(\"true\" == \"true\") && ($RELEASE_JOB == \"yes\") && ($NIGHTLY == null) && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\")",
+ "if": "(\"true\" == \"true\") && ($RELEASE_JOB == \"yes\") && ($NIGHTLY == null)",
"when": "on_success"
}
],
@@ -2774,7 +2836,7 @@
],
"rules": [
{
- "if": "(\"true\" == \"true\") && ($RELEASE_JOB == \"yes\") && ($NIGHTLY == null) && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\")",
+ "if": "(\"true\" == \"true\") && ($RELEASE_JOB == \"yes\") && ($NIGHTLY == null)",
"when": "on_success"
}
],
@@ -2840,7 +2902,7 @@
],
"rules": [
{
- "if": "(\"true\" == \"true\") && ($RELEASE_JOB == \"yes\") && ($NIGHTLY == null) && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\")",
+ "if": "(\"true\" == \"true\") && ($RELEASE_JOB == \"yes\") && ($NIGHTLY == null)",
"when": "on_success"
}
],
@@ -2904,7 +2966,7 @@
],
"rules": [
{
- "if": "(\"true\" == \"true\") && ($RELEASE_JOB == \"yes\") && ($NIGHTLY == null) && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\")",
+ "if": "(\"true\" == \"true\") && ($RELEASE_JOB == \"yes\") && ($NIGHTLY == null)",
"when": "on_success"
}
],
@@ -2968,7 +3030,7 @@
],
"rules": [
{
- "if": "(\"true\" == \"true\") && ($RELEASE_JOB == \"yes\") && ($NIGHTLY == null) && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\")",
+ "if": "(\"true\" == \"true\") && ($RELEASE_JOB == \"yes\") && ($NIGHTLY == null)",
"when": "on_success"
}
],
@@ -3032,7 +3094,7 @@
],
"rules": [
{
- "if": "(\"true\" == \"true\") && ($RELEASE_JOB == \"yes\") && ($NIGHTLY == null) && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\")",
+ "if": "(\"true\" == \"true\") && ($RELEASE_JOB == \"yes\") && ($NIGHTLY == null)",
"when": "on_success"
}
],
@@ -3096,7 +3158,7 @@
],
"rules": [
{
- "if": "(\"true\" == \"true\") && ($RELEASE_JOB == \"yes\") && ($NIGHTLY == null) && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\")",
+ "if": "(\"true\" == \"true\") && ($RELEASE_JOB == \"yes\") && ($NIGHTLY == null)",
"when": "on_success"
}
],
@@ -3160,7 +3222,7 @@
],
"rules": [
{
- "if": "(\"true\" == \"true\") && ($RELEASE_JOB == \"yes\") && ($NIGHTLY == null) && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\")",
+ "if": "(\"true\" == \"true\") && ($RELEASE_JOB == \"yes\") && ($NIGHTLY == null)",
"when": "on_success"
}
],
@@ -3224,7 +3286,7 @@
],
"rules": [
{
- "if": "(\"true\" == \"true\") && ($RELEASE_JOB == \"yes\") && ($NIGHTLY == null) && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\")",
+ "if": "(\"true\" == \"true\") && ($RELEASE_JOB == \"yes\") && ($NIGHTLY == null)",
"when": "on_success"
}
],
@@ -3290,7 +3352,7 @@
],
"rules": [
{
- "if": "(\"true\" == \"true\") && ($RELEASE_JOB == \"yes\") && ($NIGHTLY == null) && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\")",
+ "if": "(\"true\" == \"true\") && ($RELEASE_JOB == \"yes\") && ($NIGHTLY == null)",
"when": "on_success"
}
],
@@ -3356,7 +3418,7 @@
],
"rules": [
{
- "if": "(\"true\" == \"true\") && ($RELEASE_JOB == \"yes\") && ($NIGHTLY == null) && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\")",
+ "if": "(\"true\" == \"true\") && ($RELEASE_JOB == \"yes\") && ($NIGHTLY == null)",
"when": "on_success"
}
],
@@ -3422,7 +3484,7 @@
],
"rules": [
{
- "if": "(\"true\" == \"true\") && ($RELEASE_JOB == \"yes\") && ($NIGHTLY == null) && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\")",
+ "if": "(\"true\" == \"true\") && ($RELEASE_JOB == \"yes\") && ($NIGHTLY == null)",
"when": "on_success"
}
],
@@ -3486,7 +3548,7 @@
],
"rules": [
{
- "if": "(\"true\" == \"true\") && ($RELEASE_JOB == \"yes\") && ($NIGHTLY == null) && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\")",
+ "if": "(\"true\" == \"true\") && ($RELEASE_JOB == \"yes\") && ($NIGHTLY == null)",
"when": "on_success"
}
],
@@ -3550,7 +3612,7 @@
],
"rules": [
{
- "if": "(\"true\" == \"true\") && ($RELEASE_JOB == \"yes\") && ($NIGHTLY == null) && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\")",
+ "if": "(\"true\" == \"true\") && ($RELEASE_JOB == \"yes\") && ($NIGHTLY == null)",
"when": "on_success"
}
],
@@ -3610,7 +3672,7 @@
],
"rules": [
{
- "if": "(\"true\" == \"true\") && ($RELEASE_JOB == \"yes\") && ($NIGHTLY == null) && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\")",
+ "if": "(\"true\" == \"true\") && ($RELEASE_JOB == \"yes\") && ($NIGHTLY == null)",
"when": "on_success"
}
],
@@ -3673,7 +3735,7 @@
],
"rules": [
{
- "if": "(\"true\" == \"true\") && ($RELEASE_JOB == \"yes\") && ($NIGHTLY == null) && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\")",
+ "if": "(\"true\" == \"true\") && ($RELEASE_JOB == \"yes\") && ($NIGHTLY == null)",
"when": "on_success"
}
],
@@ -3740,7 +3802,7 @@
],
"rules": [
{
- "if": "(($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/)) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null) && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\")",
+ "if": "((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/)) || ($CI_MERGE_REQUEST_LABELS =~ /.*test-primops.*/)) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
"when": "on_success"
}
],
@@ -3808,7 +3870,7 @@
],
"rules": [
{
- "if": "(($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/)) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null) && (\"true\" == \"true\") && ($CI_MERGE_REQUEST_LABELS =~ /.*FreeBSD.*/) && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\")",
+ "if": "(($CI_MERGE_REQUEST_LABELS =~ /.*FreeBSD.*/)) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
"when": "on_success"
}
],
@@ -3871,7 +3933,7 @@
],
"rules": [
{
- "if": "(($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/)) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null) && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\")",
+ "if": "((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
"when": "on_success"
}
],
@@ -3935,7 +3997,7 @@
],
"rules": [
{
- "if": "(($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/)) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null) && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\")",
+ "if": "((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
"when": "on_success"
}
],
@@ -3999,7 +4061,7 @@
"rules": [
{
"allow_failure": true,
- "if": "(($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/)) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null) && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\")",
+ "if": "((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
"when": "manual"
}
],
@@ -4063,7 +4125,7 @@
"rules": [
{
"allow_failure": true,
- "if": "(($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/)) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null) && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\")",
+ "if": "((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
"when": "manual"
}
],
@@ -4126,7 +4188,7 @@
],
"rules": [
{
- "if": "(($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/)) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null) && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\")",
+ "if": "((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
"when": "on_success"
}
],
@@ -4188,7 +4250,7 @@
"rules": [
{
"allow_failure": true,
- "if": "(($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/)) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null) && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\")",
+ "if": "((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
"when": "manual"
}
],
@@ -4249,7 +4311,7 @@
],
"rules": [
{
- "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null) && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\")",
+ "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
"when": "on_success"
}
],
@@ -4311,7 +4373,7 @@
],
"rules": [
{
- "if": "(($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/)) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null) && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\")",
+ "if": "((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
"when": "on_success"
}
],
@@ -4372,7 +4434,7 @@
],
"rules": [
{
- "if": "(($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/)) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null) && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\")",
+ "if": "((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/)) || ($CI_MERGE_REQUEST_LABELS =~ /.*test-primops.*/)) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
"when": "on_success"
}
],
@@ -4433,7 +4495,7 @@
],
"rules": [
{
- "if": "(($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/)) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null) && ($CI_MERGE_REQUEST_LABELS =~ /.*LLVM backend.*/) && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\")",
+ "if": "(($CI_MERGE_REQUEST_LABELS =~ /.*LLVM backend.*/)) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
"when": "on_success"
}
],
@@ -4495,7 +4557,7 @@
"rules": [
{
"allow_failure": true,
- "if": "(($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/)) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null) && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\")",
+ "if": "((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
"when": "manual"
}
],
@@ -4558,7 +4620,7 @@
],
"rules": [
{
- "if": "(($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/)) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null) && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && ($CI_MERGE_REQUEST_LABELS =~ /.*IPE.*/) && (\"true\" == \"true\")",
+ "if": "(($CI_MERGE_REQUEST_LABELS =~ /.*IPE.*/)) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
"when": "on_success"
}
],
@@ -4619,7 +4681,7 @@
],
"rules": [
{
- "if": "(($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/)) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null) && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\")",
+ "if": "((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
"when": "on_success"
}
],
@@ -4682,7 +4744,7 @@
],
"rules": [
{
- "if": "(($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/)) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null) && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\")",
+ "if": "((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
"when": "on_success"
}
],
@@ -4746,7 +4808,7 @@
],
"rules": [
{
- "if": "(($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/)) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null) && (\"true\" == \"true\") && (\"true\" == \"true\") && ($CI_MERGE_REQUEST_LABELS =~ /.*non-moving GC.*/) && (\"true\" == \"true\") && (\"true\" == \"true\")",
+ "if": "(($CI_MERGE_REQUEST_LABELS =~ /.*non-moving GC.*/)) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
"when": "on_success"
}
],
@@ -4807,7 +4869,7 @@
],
"rules": [
{
- "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null) && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\")",
+ "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
"when": "on_success"
}
],
@@ -4866,7 +4928,7 @@
],
"rules": [
{
- "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null) && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\") && (\"true\" == \"true\")",
+ "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
"when": "on_success"
}
],
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/523a25a2d62d8c29589470efbddafc13de27f631...7b28b11d074950b2958502d20dcab27ec9a8bbcc
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/523a25a2d62d8c29589470efbddafc13de27f631...7b28b11d074950b2958502d20dcab27ec9a8bbcc
You're receiving this email because of your account on gitlab.haskell.org.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20230806/698f3dae/attachment-0001.html>
More information about the ghc-commits
mailing list