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