Skip to content
Snippets Groups Projects
Commit 8cd99d8f authored by bardur.arantsson's avatar bardur.arantsson Committed by GitHub
Browse files

Merge pull request #4086 from ezyang/pr/T4081

Improve error output when package fails to build.
parents 915ca233 da9c0526
No related branches found
No related tags found
No related merge requests found
......@@ -751,7 +751,7 @@ dieOnBuildFailures verbosity plan buildOutcomes
++ " because it depends on " ++ display depid
++ " which itself failed to build"
where
pkgstr = display (packageId pkg)
pkgstr = elabConfiguredName verbosity pkg
++ if mentionDepOf
then renderDependencyOf (installedUnitId pkg)
else ""
......@@ -765,11 +765,11 @@ dieOnBuildFailures verbosity plan buildOutcomes
renderDependencyOf pkgid =
case ultimateDeps pkgid of
[] -> ""
(p1:[]) -> " (which is required by " ++ display (packageName p1) ++ ")"
(p1:p2:[]) -> " (which is required by " ++ display (packageName p1)
++ " and " ++ display (packageName p2) ++ ")"
(p1:p2:_) -> " (which is required by " ++ display (packageName p1)
++ ", " ++ display (packageName p2)
(p1:[]) -> " (which is required by " ++ elabPlanPackageName verbosity p1 ++ ")"
(p1:p2:[]) -> " (which is required by " ++ elabPlanPackageName verbosity p1
++ " and " ++ elabPlanPackageName verbosity p2 ++ ")"
(p1:p2:_) -> " (which is required by " ++ elabPlanPackageName verbosity p1
++ ", " ++ elabPlanPackageName verbosity p2
++ " and others)"
showException e = case fromException e of
......
......@@ -22,6 +22,9 @@ module Distribution.Client.ProjectPlanning.Types (
elabSetupDependencies,
elabPkgConfigDependencies,
elabPlanPackageName,
elabConfiguredName,
ElaboratedPackageOrComponent(..),
ElaboratedComponent(..),
ElaboratedPackage(..),
......@@ -46,7 +49,7 @@ import Distribution.Client.PackageHash
import Distribution.Client.Types
import Distribution.Client.InstallPlan
( GenericInstallPlan, GenericPlanPackage )
( GenericInstallPlan, GenericPlanPackage(..) )
import Distribution.Client.SolverInstallPlan
( SolverInstallPlan )
import Distribution.Client.DistDirLayout
......@@ -54,6 +57,8 @@ import Distribution.Client.DistDirLayout
import Distribution.Backpack
import Distribution.Backpack.ModuleShape
import Distribution.Verbosity
import Distribution.Text
import Distribution.Types.ComponentRequestedSpec
import Distribution.Package
hiding (InstalledPackageId, installedPackageId)
......@@ -100,6 +105,16 @@ type ElaboratedPlanPackage
= GenericPlanPackage InstalledPackageInfo
ElaboratedConfiguredPackage
-- | User-friendly display string for an 'ElaboratedPlanPackage'.
elabPlanPackageName :: Verbosity -> ElaboratedPlanPackage -> String
elabPlanPackageName verbosity (PreExisting ipkg)
| verbosity <= normal = display (packageName ipkg)
| otherwise = display (installedUnitId ipkg)
elabPlanPackageName verbosity (Configured elab)
= elabConfiguredName verbosity elab
elabPlanPackageName verbosity (Installed elab)
= elabConfiguredName verbosity elab
--TODO: [code cleanup] decide if we really need this, there's not much in it, and in principle
-- even platform and compiler could be different if we're building things
-- like a server + client with ghc + ghcjs
......@@ -290,6 +305,21 @@ data ElaboratedPackageOrComponent
instance Binary ElaboratedPackageOrComponent
-- | A user-friendly descriptor for an 'ElaboratedConfiguredPackage'.
elabConfiguredName :: Verbosity -> ElaboratedConfiguredPackage -> String
elabConfiguredName verbosity elab
| verbosity <= normal
= (case elabPkgOrComp elab of
ElabPackage _ -> ""
ElabComponent comp ->
case compComponentName comp of
Nothing -> "setup from "
Just CLibName -> ""
Just cname -> display cname ++ " from ")
++ display (packageId elab)
| otherwise
= display (elabUnitId elab)
elabDistDirParams :: ElaboratedSharedConfig -> ElaboratedConfiguredPackage -> DistDirParams
elabDistDirParams shared elab = DistDirParams {
distParamUnitId = installedUnitId elab,
......
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