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

Track broken package on a per-unit basis

parent 47654ece
No related tags found
No related merge requests found
Pipeline #12156 failed
......@@ -123,14 +123,10 @@ testPatches cfg = do
print $ resultSummary (configExpectedBrokenPkgs cfg) runResult
BSL.writeFile "results.json" . encode =<< writeLogs "logs" runResult
case failedPatches (configExpectedBrokenPkgs cfg) runResult of
[] -> return ()
badPatches -> do
print $ "Failed due to unexpected failures in:" PP.<$$> PP.indent 2 (
vcat [ prettyPkgVer (patchedPackageName tp) (patchedPackageVersion tp)
| tp <- badPatches
])
exitWith $ ExitFailure 1
let failedBuilds = failedPatches runResult
planningFailures = planningErrors runResult
okay = null failedBuilds && null planningFailures
unless okay $ exitWith $ ExitFailure 1
writeLogs :: FilePath -> RunResult LogOutput -> IO (RunResult ())
writeLogs logDir runResult = do
......@@ -149,26 +145,28 @@ writeLogs logDir runResult = do
writeLog (UnitId unitId, LogOutput log) = TIO.writeFile logPath log
where logPath = logDir </> T.unpack unitId
failedPatches :: BrokenPackages -> RunResult log -> [TestedPatch log]
failedPatches broken (RunResult testedPatches) =
filter failed testedPatches
failedUnits :: BrokenPackages -> RunResult log
-> M.Map UnitId (BuildInfo, BuildResult log)
failedUnits broken = M.filter didFail . runResultUnits
where
failed tp =
patchFailed tp /= failureExpected broken (patchedPackageName tp)
patchFailed :: TestedPatch log -> Bool
patchFailed tp =
case patchedPackageResult tp of
PackagePlanningFailed _ -> True
PackageResult False _ -> True
_ -> False
didFail (buildInfo, result) =
case result of
BuildFailed _ -> not $ failureExpected broken (pkgName buildInfo)
_ -> False
planningErrors :: RunResult log -> [(PkgName, Ver)]
planningErrors runResult =
[ (patchedPackageName tpatch, patchedPackageVersion tpatch)
| tpatch <- testedPatches runResult
, PackagePlanningFailed _ <- pure $ patchedPackageResult tpatch
]
resultSummary :: forall log. BrokenPackages -> RunResult log -> Doc
resultSummary broken runResult = vcat
[ "Total units built:" <+> pshow (length allUnits)
, ""
, pshow (length planningErrors) <+> "had no valid install plan:"
, PP.indent 4 $ vcat $ map (uncurry prettyPkgVer) planningErrors
, PP.indent 4 $ vcat $ map (uncurry prettyPkgVer) (planningErrors runResult)
, ""
, pshow (length failedUnits) <+> "units failed to build:"
, PP.indent 4 $ vcat
......@@ -182,13 +180,6 @@ resultSummary broken runResult = vcat
, pshow (length failedDependsUnits) <+> "units failed to build due to unbuildable dependencies."
]
where
planningErrors :: [(PkgName, Ver)]
planningErrors =
[ (patchedPackageName tpatch, patchedPackageVersion tpatch)
| tpatch <- testedPatches runResult
, PackagePlanningFailed _ <- pure $ patchedPackageResult tpatch
]
allUnits = runResultUnits runResult
failedUnits :: M.Map UnitId (BuildInfo, BuildResult log)
......
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