diff --git a/cabal-install/Distribution/Client/CmdBuild.hs b/cabal-install/Distribution/Client/CmdBuild.hs index caf229534e430e2d2e4667a48b5ca75a5a1fabd6..8a5afe80c8606417749f571ae57e1734d4f4c187 100644 --- a/cabal-install/Distribution/Client/CmdBuild.hs +++ b/cabal-install/Distribution/Client/CmdBuild.hs @@ -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) diff --git a/cabal-install/Distribution/Client/CmdRepl.hs b/cabal-install/Distribution/Client/CmdRepl.hs index bfb0afef94ad77df5a6aff6623f8d51f3ea72c7a..e277f50147ac26428c6fdf074be5ea8bf7cb84ab 100644 --- a/cabal-install/Distribution/Client/CmdRepl.hs +++ b/cabal-install/Distribution/Client/CmdRepl.hs @@ -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) diff --git a/cabal-install/Distribution/Client/ProjectOrchestration.hs b/cabal-install/Distribution/Client/ProjectOrchestration.hs index 85e0d86cf2a296e0f46b23e88c409230db9f8e8a..969b3a6e975744a84f0595e8234f633f38da59e0 100644 --- a/cabal-install/Distribution/Client/ProjectOrchestration.hs +++ b/cabal-install/Distribution/Client/ProjectOrchestration.hs @@ -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 +