Skip to content

Commit a239ea7

Browse files
committed
Show UnknownPackage plan construction errors unless redundant #3172
1 parent a41a1c7 commit a239ea7

File tree

2 files changed

+23
-9
lines changed

2 files changed

+23
-9
lines changed

src/Stack/Build/ConstructPlan.hs

Lines changed: 19 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,4 @@
1+
{-# OPTIONS_GHC -fno-warn-orphans #-}
12
{-# LANGUAGE ConstraintKinds #-}
23
{-# LANGUAGE DeriveDataTypeable #-}
34
{-# LANGUAGE DeriveGeneric #-}
@@ -10,6 +11,7 @@
1011
{-# LANGUAGE TemplateHaskell #-}
1112
{-# LANGUAGE TupleSections #-}
1213
{-# LANGUAGE ViewPatterns #-}
14+
{-# LANGUAGE StandaloneDeriving #-}
1315
-- | Construct a @Plan@ for how to build
1416
module Stack.Build.ConstructPlan
1517
( constructPlan
@@ -25,6 +27,7 @@ import Control.Monad.Trans.Resource
2527
import Data.Either
2628
import Data.Function
2729
import Data.List
30+
import Data.List.Extra (nubOrd)
2831
import Data.Map.Strict (Map)
2932
import qualified Data.Map.Strict as M
3033
import qualified Data.Map.Strict as Map
@@ -892,7 +895,9 @@ data ConstructPlanException
892895
| DependencyPlanFailures Package (Map PackageName (VersionRange, LatestApplicableVersion, BadDependency))
893896
| UnknownPackage PackageName -- TODO perhaps this constructor will be removed, and BadDependency will handle it all
894897
-- ^ Recommend adding to extra-deps, give a helpful version number?
895-
deriving (Typeable, Eq, Show)
898+
deriving (Typeable, Eq, Ord, Show)
899+
900+
deriving instance Ord VersionRange
896901

897902
-- | For display purposes only, Nothing if package not found
898903
type LatestApplicableVersion = Maybe Version
@@ -902,7 +907,7 @@ data BadDependency
902907
= NotInBuildPlan
903908
| Couldn'tResolveItsDependencies Version
904909
| DependencyMismatch Version
905-
deriving (Typeable, Eq, Show)
910+
deriving (Typeable, Eq, Ord, Show)
906911

907912
-- TODO: Consider intersecting version ranges for multiple deps on a
908913
-- package. This is why VersionRange is in the parent map.
@@ -926,7 +931,7 @@ pprintExceptions exceptions stackYaml parentMap wanted =
926931
line <>
927932
"You may also want to try the 'stack solver' command"
928933
where
929-
exceptions' = nub exceptions
934+
exceptions' = nubOrd exceptions
930935

931936
extras = Map.unions $ map getExtras exceptions'
932937
getExtras (DependencyCycleDetected _) = Map.empty
@@ -940,11 +945,16 @@ pprintExceptions exceptions stackYaml parentMap wanted =
940945
pprintExtra (name, version) =
941946
fromString (concat ["- ", packageNameString name, "-", versionString version])
942947

948+
allNotInBuildPlan = Set.fromList $ concatMap toNotInBuildPlan exceptions'
949+
toNotInBuildPlan (DependencyPlanFailures _ pDeps) =
950+
map fst $ filter (\(_, (_, _, badDep)) -> badDep == NotInBuildPlan) $ Map.toList pDeps
951+
toNotInBuildPlan _ = []
952+
943953
pprintException (DependencyCycleDetected pNames) = Just $
944954
"Dependency cycle detected in packages:" <> line <>
945955
indent 4 (encloseSep "[" "]" "," (map (errorRed . fromString . packageNameString) pNames))
946-
pprintException (DependencyPlanFailures pkg (Map.toList -> pDeps)) =
947-
case mapMaybe pprintDep pDeps of
956+
pprintException (DependencyPlanFailures pkg pDeps) =
957+
case mapMaybe pprintDep (Map.toList pDeps) of
948958
[] -> Nothing
949959
depErrors -> Just $
950960
"In the dependencies for" <+> pkgIdent <>
@@ -961,9 +971,10 @@ pprintExceptions exceptions stackYaml parentMap wanted =
961971
[pkgIdent]
962972
where
963973
pkgIdent = displayCurrentPkgId (packageIdentifier pkg)
964-
-- TODO: optionally show these?
965-
-- Skip these because they are redundant with 'NotInBuildPlan' info.
966-
pprintException (UnknownPackage _) = Nothing
974+
-- Skip these when they are redundant with 'NotInBuildPlan' info.
975+
pprintException (UnknownPackage name)
976+
| name `Set.member` allNotInBuildPlan = Nothing
977+
| otherwise = Just $ "Unknown package:" <+> displayCurrentPkgName name
967978

968979
pprintFlags flags
969980
| Map.null flags = ""

src/Stack/PrettyPrint.hs

Lines changed: 4 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -15,7 +15,7 @@ module Stack.PrettyPrint
1515
-- | These are preferred to colors directly, so that we can
1616
-- encourage consistency of color meanings.
1717
, errorRed, goodGreen, shellMagenta
18-
, displayTargetPkgId, displayCurrentPkgId, displayErrorPkgId
18+
, displayTargetPkgId, displayCurrentPkgId, displayCurrentPkgName, displayErrorPkgId
1919
, displayMilliseconds
2020
-- * Formatting utils
2121
, bulletedList
@@ -113,6 +113,9 @@ displayTargetPkgId = cyan . display
113113
displayCurrentPkgId :: PackageIdentifier -> AnsiDoc
114114
displayCurrentPkgId = yellow . display
115115

116+
displayCurrentPkgName :: PackageName -> AnsiDoc
117+
displayCurrentPkgName = yellow . display
118+
116119
displayErrorPkgId :: PackageIdentifier -> AnsiDoc
117120
displayErrorPkgId = errorRed . display
118121

0 commit comments

Comments
 (0)