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
@@ -24,7 +26,9 @@ import Control.Monad.State.Strict (execState)
2426import Control.Monad.Trans.Resource
2527import Data.Either
2628import Data.Function
29+ import qualified Data.HashSet as HashSet
2730import Data.List
31+ import Data.List.Extra (nubOrd )
2832import Data.Map.Strict (Map )
2933import qualified Data.Map.Strict as M
3034import qualified Data.Map.Strict as Map
@@ -892,7 +896,9 @@ data ConstructPlanException
892896 | DependencyPlanFailures Package (Map PackageName (VersionRange , LatestApplicableVersion , BadDependency ))
893897 | UnknownPackage PackageName -- TODO perhaps this constructor will be removed, and BadDependency will handle it all
894898 -- ^ Recommend adding to extra-deps, give a helpful version number?
895- deriving (Typeable , Eq , Show )
899+ deriving (Typeable , Eq , Ord , Show )
900+
901+ deriving instance Ord VersionRange
896902
897903-- | For display purposes only, Nothing if package not found
898904type LatestApplicableVersion = Maybe Version
@@ -902,7 +908,7 @@ data BadDependency
902908 = NotInBuildPlan
903909 | Couldn'tResolveItsDependencies Version
904910 | DependencyMismatch Version
905- deriving (Typeable , Eq , Show )
911+ deriving (Typeable , Eq , Ord , Show )
906912
907913-- TODO: Consider intersecting version ranges for multiple deps on a
908914-- package. This is why VersionRange is in the parent map.
@@ -926,7 +932,7 @@ pprintExceptions exceptions stackYaml parentMap wanted =
926932 line <>
927933 " You may also want to try the 'stack solver' command"
928934 where
929- exceptions' = nub exceptions
935+ exceptions' = nubOrd exceptions
930936
931937 extras = Map. unions $ map getExtras exceptions'
932938 getExtras (DependencyCycleDetected _) = Map. empty
@@ -940,11 +946,16 @@ pprintExceptions exceptions stackYaml parentMap wanted =
940946 pprintExtra (name, version) =
941947 fromString (concat [" - " , packageNameString name, " -" , versionString version])
942948
949+ allNotInBuildPlan = Set. fromList $ concatMap toNotInBuildPlan exceptions'
950+ toNotInBuildPlan (DependencyPlanFailures _ pDeps) =
951+ map fst $ filter (\ (_, (_, _, badDep)) -> badDep == NotInBuildPlan ) $ Map. toList pDeps
952+ toNotInBuildPlan _ = []
953+
943954 pprintException (DependencyCycleDetected pNames) = Just $
944955 " Dependency cycle detected in packages:" <> line <>
945956 indent 4 (encloseSep " [" " ]" " ," (map (errorRed . fromString . packageNameString) pNames))
946- pprintException (DependencyPlanFailures pkg ( Map. toList -> pDeps) ) =
947- case mapMaybe pprintDep pDeps of
957+ pprintException (DependencyPlanFailures pkg pDeps) =
958+ case mapMaybe pprintDep ( Map. toList pDeps) of
948959 [] -> Nothing
949960 depErrors -> Just $
950961 " In the dependencies for" <+> pkgIdent <>
@@ -961,9 +972,12 @@ pprintExceptions exceptions stackYaml parentMap wanted =
961972 [pkgIdent]
962973 where
963974 pkgIdent = displayCurrentPkgId (packageIdentifier pkg)
964- -- TODO: optionally show these?
965- -- Skip these because they are redundant with 'NotInBuildPlan' info.
966- pprintException (UnknownPackage _) = Nothing
975+ -- Skip these when they are redundant with 'NotInBuildPlan' info.
976+ pprintException (UnknownPackage name)
977+ | name `Set.member` allNotInBuildPlan = Nothing
978+ | name `HashSet.member` wiredInPackages =
979+ Just $ " Can't build a package with same name as a wired-in-package:" <+> displayCurrentPkgName name
980+ | otherwise = Just $ " Unknown package:" <+> displayCurrentPkgName name
967981
968982 pprintFlags flags
969983 | Map. null flags = " "
0 commit comments