1+ {-# OPTIONS_GHC -fno-warn-orphans #-}
12{-# LANGUAGE ConstraintKinds #-}
23{-# LANGUAGE DeriveDataTypeable #-}
34{-# LANGUAGE DeriveGeneric #-}
1011{-# LANGUAGE TemplateHaskell #-}
1112{-# LANGUAGE TupleSections #-}
1213{-# LANGUAGE ViewPatterns #-}
14+ {-# LANGUAGE StandaloneDeriving #-}
1315-- | Construct a @Plan@ for how to build
1416module Stack.Build.ConstructPlan
1517 ( constructPlan
@@ -25,6 +27,7 @@ import Control.Monad.Trans.Resource
2527import Data.Either
2628import Data.Function
2729import Data.List
30+ import Data.List.Extra (nubOrd )
2831import Data.Map.Strict (Map )
2932import qualified Data.Map.Strict as M
3033import 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
898903type 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 = " "
0 commit comments