Skip to content
Snippets Groups Projects
Commit 5fe5202b authored by Duncan Coutts's avatar Duncan Coutts
Browse files

Rework reportBuildFailures to include build logs

Reporting build logs is important as we otherwise have no real info for
why deps failed to build. It does make the presentation more difficult
however because build logs can be long and in principle there can be
several, which means it can take up more than a single screen in a
console. The first thing users notice is typically the last few
messages, so in the case that we're presenting long build logs then its
important to also include a short summary at the end.

So our approach is this: for packages where we want to show a build log,
we dump those first, in full, each with a header to indicate which
package it is, log file name (for later reference), plus any extra
detail we have from the phase of the failure or the exception. Then
after all build logs we end with a short summary of the failure(s). For
packages where we do not show a build log (e.g. local packages that dump
live to the console) we only present a summary at the end, but we
include a little more detail than for the packages that had a build log
since this is the only thing we report for them. So we include details
of the exception.
parent bfdd9539
No related branches found
No related tags found
No related merge requests found
......@@ -55,7 +55,7 @@ buildAction (configFlags, configExFlags, installFlags, haddockFlags)
unless (buildSettingDryRun buildSettings) $ do
buildResults <- runProjectBuildPhase verbosity buildCtx
reportBuildFailures elaboratedPlan buildResults
reportBuildFailures verbosity elaboratedPlan buildResults
where
verbosity = fromFlagOrDefault normal (configVerbosity configFlags)
......
......@@ -59,7 +59,7 @@ replAction (configFlags, configExFlags, installFlags, haddockFlags)
unless (buildSettingDryRun buildSettings) $ do
buildResults <- runProjectBuildPhase verbosity buildCtx
reportBuildFailures elaboratedPlan buildResults
reportBuildFailures verbosity elaboratedPlan buildResults
where
verbosity = fromFlagOrDefault normal (configVerbosity configFlags)
......
......@@ -86,6 +86,7 @@ import Distribution.Text
import qualified Data.Set as Set
import qualified Data.Map as Map
import Data.Map (Map)
import qualified Data.ByteString.Lazy.Char8 as BS
import Data.List
import Data.Maybe
import Data.Either
......@@ -474,35 +475,66 @@ printPlan verbosity
showMonitorChangedReason MonitorCorruptCache = "cannot read state cache"
reportBuildFailures :: ElaboratedInstallPlan -> BuildOutcomes -> IO ()
reportBuildFailures plan buildOutcomes
| null failures
= return ()
| isSimpleCase
= exitFailure
| otherwise
= case failuresPrimary of
[(pkg, failure)] -> die $ renderFailure pkg (buildFailureReason failure)
multiple -> die $ "multiple failures:\n"
++ unlines
[ renderFailure pkg (buildFailureReason failure)
| (pkg, failure) <- multiple ]
reportBuildFailures :: Verbosity -> ElaboratedInstallPlan -> BuildOutcomes -> IO ()
reportBuildFailures verbosity plan buildOutcomes
| null failures = return ()
| isSimpleCase = exitFailure
| otherwise = do
-- For failures where we have a build log, print the log plus a header
sequence_
[ do notice verbosity $
'\n' : renderFailureDetail False pkg reason
++ "\nBuild log ( " ++ logfile ++ " ):"
BS.readFile logfile >>= BS.putStrLn
| verbosity >= normal
, (pkg, ShowBuildSummaryAndLog reason logfile)
<- failuresClassification
]
-- For all failures, print either a short summary (if we showed the
-- build log) or all details
die $ unlines
[ case failureClassification of
ShowBuildSummaryAndLog reason _
| verbosity > normal
-> renderFailureDetail mentionDepOf pkg reason
| otherwise
-> renderFailureSummary mentionDepOf pkg reason
ShowBuildSummaryOnly reason ->
renderFailureDetail mentionDepOf pkg reason
| let mentionDepOf = verbosity <= normal
, (pkg, failureClassification) <- failuresClassification ]
where
failures = [ (pkgid, failure)
| (pkgid, Left failure) <- Map.toList buildOutcomes ]
failuresPrimary =
[ (pkg, failure)
failuresClassification =
[ (pkg, classifyBuildFailure failure)
| (pkgid, failure) <- failures
, case buildFailureReason failure of
DependentFailed {} -> False
DependentFailed {} -> verbosity > normal
_ -> True
, InstallPlan.Configured pkg <-
maybeToList (InstallPlan.lookup plan pkgid)
]
classifyBuildFailure :: BuildFailure -> BuildFailurePresentation
classifyBuildFailure BuildFailure {
buildFailureReason = reason,
buildFailureLogFile = mlogfile
} =
maybe (ShowBuildSummaryOnly reason)
(ShowBuildSummaryAndLog reason) $ do
logfile <- mlogfile
e <- buildFailureException reason
ExitFailure 1 <- fromException e
return logfile
-- Special case: we don't want to report anything complicated in the case
-- of just doing build on the current package, since it's clear from
-- context which package failed.
......@@ -543,33 +575,36 @@ reportBuildFailures plan buildOutcomes
hasNoDependents :: HasUnitId pkg => pkg -> Bool
hasNoDependents = null . InstallPlan.revDirectDeps plan . installedUnitId
renderFailure pkg reason =
renderFailureDetail mentionDepOf pkg reason =
renderFailureSummary mentionDepOf pkg reason ++ "."
++ renderFailureExtraDetail reason
++ maybe "" showException (buildFailureException reason)
renderFailureSummary mentionDepOf pkg reason =
case reason of
DownloadFailed e -> "failed to download " ++ pkgstr ++ "."
++ showException e
UnpackFailed e -> "failed to unpack " ++ pkgstr ++ "."
++ showException e
ConfigureFailed e -> "failed to build " ++ pkgstr ++ ". The failure"
++ "occurred during the configure step."
++ showException e
BuildFailed e -> "failed to build " ++ pkgstr ++ "."
++ showException e
ReplFailed e -> "repl failed for " ++ pkgstr ++ "."
++ showException e
HaddocksFailed e -> "failed to build documentation for " ++ pkgstr ++ "."
++ showException e
TestsFailed e -> "tests failed for " ++ pkgstr ++ "."
++ showException e
InstallFailed e -> "failed to build " ++ pkgstr ++ ". The failure"
++ "occurred during the final install step."
++ showException e
-- This will never happen, but we include it for completeness
DependentFailed pkgid -> " depends on " ++ display pkgid
++ " which failed to install."
DownloadFailed _ -> "Failed to download " ++ pkgstr
UnpackFailed _ -> "Failed to unpack " ++ pkgstr
ConfigureFailed _ -> "Failed to build " ++ pkgstr
BuildFailed _ -> "Failed to build " ++ pkgstr
ReplFailed _ -> "repl failed for " ++ pkgstr
HaddocksFailed _ -> "Failed to build documentation for " ++ pkgstr
TestsFailed _ -> "Tests failed for " ++ pkgstr
InstallFailed _ -> "Failed to build " ++ pkgstr
DependentFailed depid
-> "Failed to build " ++ display (packageId pkg)
++ " because it depends on " ++ display depid
++ " which itself failed to build"
where
pkgstr = display (packageId pkg)
++ renderDependencyOf (installedUnitId pkg)
++ if mentionDepOf
then renderDependencyOf (installedUnitId pkg)
else ""
renderFailureExtraDetail reason =
case reason of
ConfigureFailed _ -> " The failure occurred during the configure step."
InstallFailed _ -> " The failure occurred during the final install step."
_ -> ""
renderDependencyOf pkgid =
case ultimateDeps pkgid of
......@@ -583,7 +618,6 @@ reportBuildFailures plan buildOutcomes
showException e = case fromException e of
Just (ExitFailure 1) -> ""
--TODO: show log in this case
#ifdef MIN_VERSION_unix
Just (ExitFailure n)
......@@ -596,7 +630,7 @@ reportBuildFailures plan buildOutcomes
++ "(i.e. SIGKILL). " ++ explanation
where
explanation = "The typical reason for this is that there is not "
++ "enough memory available (so the OS kills a process "
++ "enough memory available (e.g. the OS killed a process "
++ "using lots of memory)."
#endif
Just (ExitFailure n) ->
......@@ -609,3 +643,19 @@ reportBuildFailures plan buildOutcomes
++ show e
#endif
buildFailureException reason =
case reason of
DownloadFailed e -> Just e
UnpackFailed e -> Just e
ConfigureFailed e -> Just e
BuildFailed e -> Just e
ReplFailed e -> Just e
HaddocksFailed e -> Just e
TestsFailed e -> Just e
InstallFailed e -> Just e
DependentFailed _ -> Nothing
data BuildFailurePresentation =
ShowBuildSummaryOnly BuildFailureReason
| ShowBuildSummaryAndLog BuildFailureReason FilePath
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