From 5fb5efdad13bbf9e4f1eb85793e807d0fff86fc1 Mon Sep 17 00:00:00 2001
From: Oleg Grenrus <oleg.grenrus@iki.fi>
Date: Sat, 2 Jan 2021 01:50:49 +0200
Subject: [PATCH] Improve reporting when Broken package is found

---
 cabal-install/Distribution/Client/ProjectPlanning.hs   |  2 +-
 .../Distribution/Solver/Modular/IndexConversion.hs     | 10 +++++-----
 cabal-install/Distribution/Solver/Modular/Message.hs   |  2 +-
 cabal-install/Distribution/Solver/Modular/Tree.hs      |  3 ++-
 4 files changed, 9 insertions(+), 8 deletions(-)

diff --git a/cabal-install/Distribution/Client/ProjectPlanning.hs b/cabal-install/Distribution/Client/ProjectPlanning.hs
index 9f63d15ecf..7b5d87cc43 100644
--- a/cabal-install/Distribution/Client/ProjectPlanning.hs
+++ b/cabal-install/Distribution/Client/ProjectPlanning.hs
@@ -2480,7 +2480,7 @@ availableSourceTargets elab =
               (Nothing,   True)  -> TargetBuildable (elabUnitId elab, cname)
                                                     TargetNotRequestedByDefault
               (Just True, False) ->
-                error "componentAvailableTargetStatus: impossible"
+                error $ "componentAvailableTargetStatus: impossible; cname=" ++ prettyShow cname
       where
         cname      = componentName component
         buildable  = PD.buildable (componentBuildInfo component)
diff --git a/cabal-install/Distribution/Solver/Modular/IndexConversion.hs b/cabal-install/Distribution/Solver/Modular/IndexConversion.hs
index 37a34878f1..72d0b8193e 100644
--- a/cabal-install/Distribution/Solver/Modular/IndexConversion.hs
+++ b/cabal-install/Distribution/Solver/Modular/IndexConversion.hs
@@ -90,8 +90,8 @@ convId ipi = (pn, I ver $ Inst $ IPI.installedUnitId ipi)
 convIP :: SI.InstalledPackageIndex -> IPI.InstalledPackageInfo -> (PN, I, PInfo)
 convIP idx ipi =
   case traverse (convIPId (DependencyReason pn M.empty S.empty) comp idx) (IPI.depends ipi) of
-        Nothing  -> (pn, i, PInfo [] M.empty M.empty (Just Broken))
-        Just fds -> ( pn, i, PInfo fds components M.empty Nothing)
+        Left u    -> (pn, i, PInfo [] M.empty M.empty (Just (Broken u)))
+        Right fds -> (pn, i, PInfo fds components M.empty Nothing)
  where
   -- TODO: Handle sub-libraries and visibility.
   components =
@@ -141,13 +141,13 @@ convIP idx ipi =
 -- May return Nothing if the package can't be found in the index. That
 -- indicates that the original package having this dependency is broken
 -- and should be ignored.
-convIPId :: DependencyReason PN -> Component -> SI.InstalledPackageIndex -> UnitId -> Maybe (FlaggedDep PN)
+convIPId :: DependencyReason PN -> Component -> SI.InstalledPackageIndex -> UnitId -> Either UnitId (FlaggedDep PN)
 convIPId dr comp idx ipid =
   case SI.lookupUnitId idx ipid of
-    Nothing  -> Nothing
+    Nothing  -> Left ipid
     Just ipi -> let (pn, i) = convId ipi
                     name = ExposedLib LMainLibName  -- TODO: Handle sub-libraries.
-                in  Just (D.Simple (LDep dr (Dep (PkgComponent pn name) (Fixed i))) comp)
+                in  Right (D.Simple (LDep dr (Dep (PkgComponent pn name) (Fixed i))) comp)
                 -- NB: something we pick up from the
                 -- InstalledPackageIndex is NEVER an executable
 
diff --git a/cabal-install/Distribution/Solver/Modular/Message.hs b/cabal-install/Distribution/Solver/Modular/Message.hs
index 9624f76e02..126c1628e9 100644
--- a/cabal-install/Distribution/Solver/Modular/Message.hs
+++ b/cabal-install/Distribution/Solver/Modular/Message.hs
@@ -230,7 +230,7 @@ showFR _ CannotInstall                    = " (only already installed instances
 showFR _ CannotReinstall                  = " (avoiding to reinstall a package with same version but new dependencies)"
 showFR _ NotExplicit                      = " (not a user-provided goal nor mentioned as a constraint, but reject-unconstrained-dependencies was set)"
 showFR _ Shadowed                         = " (shadowed by another installed package with same version)"
-showFR _ Broken                           = " (package is broken)"
+showFR _ (Broken u)                       = " (package is broken, missing depenedency " ++ prettyShow u ++ ")"
 showFR _ UnknownPackage                   = " (unknown package)"
 showFR _ (GlobalConstraintVersion vr src) = " (" ++ constraintSource src ++ " requires " ++ prettyShow vr ++ ")"
 showFR _ (GlobalConstraintInstalled src)  = " (" ++ constraintSource src ++ " requires installed instance)"
diff --git a/cabal-install/Distribution/Solver/Modular/Tree.hs b/cabal-install/Distribution/Solver/Modular/Tree.hs
index ca7099278c..b28c0f8ff9 100644
--- a/cabal-install/Distribution/Solver/Modular/Tree.hs
+++ b/cabal-install/Distribution/Solver/Modular/Tree.hs
@@ -32,6 +32,7 @@ import Distribution.Solver.Types.ConstraintSource
 import Distribution.Solver.Types.Flag
 import Distribution.Solver.Types.PackagePath
 import Distribution.Types.PkgconfigVersionRange
+import Distribution.Types.UnitId (UnitId)
 import Language.Haskell.Extension (Extension, Language)
 
 type Weight = Double
@@ -111,7 +112,7 @@ data FailReason = UnsupportedExtension Extension
                 | CannotReinstall
                 | NotExplicit
                 | Shadowed
-                | Broken
+                | Broken UnitId
                 | UnknownPackage
                 | GlobalConstraintVersion VR ConstraintSource
                 | GlobalConstraintInstalled ConstraintSource
-- 
GitLab