From b581165562af3a350842c3bd4738515a8ab4affc Mon Sep 17 00:00:00 2001 From: Phil de Joux Date: Sun, 19 Jan 2025 19:41:44 -0500 Subject: [PATCH 1/2] Combine duplicate build tools - report the duplicate versions - intersect the version ranges --- Cabal/src/Distribution/Simple/Configure.hs | 44 +++++++++++++++++++++- 1 file changed, 42 insertions(+), 2 deletions(-) diff --git a/Cabal/src/Distribution/Simple/Configure.hs b/Cabal/src/Distribution/Simple/Configure.hs index 7c96efb33fc..48bd130c11c 100644 --- a/Cabal/src/Distribution/Simple/Configure.hs +++ b/Cabal/src/Distribution/Simple/Configure.hs @@ -1,5 +1,6 @@ {-# LANGUAGE DataKinds #-} {-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE LambdaCase #-} {-# LANGUAGE NamedFieldPuns #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE RankNTypes #-} @@ -129,7 +130,8 @@ import qualified Data.ByteString as BS import Data.ByteString.Lazy (ByteString) import qualified Data.ByteString.Lazy.Char8 as BLC8 import Data.List - ( intersect + ( groupBy + , intersect , stripPrefix , (\\) ) @@ -172,10 +174,13 @@ import qualified System.Info import Text.PrettyPrint ( Doc , char + , colon , hsep + , nest , quotes , renderStyle , text + , vcat , ($+$) ) @@ -858,7 +863,7 @@ configurePackage cfg lbc0 pkg_descr00 flags enabled comp platform programDb0 pac -- right before calling configurePackage? -- Configure certain external build tools, see below for which ones. - let requiredBuildTools + let rawRequiredBuildTools -- If --ignore-build-tools is set, no build tool is required: | fromFlagOrDefault False $ configIgnoreBuildTools cfg = [] @@ -886,6 +891,19 @@ configurePackage cfg lbc0 pkg_descr00 flags enabled comp platform programDb0 pac ] externBuildToolDeps ++ unknownBuildTools + let (requiredBuildTools, dups) = deduplicateBuildTools rawRequiredBuildTools + + for_ dups $ \case + (_, []) -> return () + (merged, ds@(dup : _)) -> + noticeDoc verbosity $ + vcat + [ (text "The build tool" <+> quotes (text $ nameOf dup) <+> "has multiple versions specified") <> colon + , nest 2 $ vcat [char '-' <+> text (prettyShow $ versionOf d) | d <- ds] + , text "These versions have been combined as" <> colon + , nest 2 $ quotes (text $ prettyShow merged) + ] + programDb1 <- configureAllKnownPrograms (lessVerbose verbosity) programDb0 >>= configureRequiredPrograms verbosity requiredBuildTools @@ -935,6 +953,28 @@ configurePackage cfg lbc0 pkg_descr00 flags enabled comp platform programDb0 pac return (lbc, pbd) +nameOf :: LegacyExeDependency -> String +nameOf (LegacyExeDependency n _) = n + +versionOf :: LegacyExeDependency -> VersionRange +versionOf (LegacyExeDependency _ v) = v + +-- | Any duplicates in the list has their version range merged by intersection. +-- The second list has the build tool with its merged version range and its list +-- of duplicates. +deduplicateBuildTools :: [LegacyExeDependency] -> ([LegacyExeDependency], [(LegacyExeDependency, [LegacyExeDependency])]) +deduplicateBuildTools xs = + catMaybes + <$> unzip + [ (merged, if length gs == 1 then Nothing else Just (merged, gs)) + | gs@(g : _) <- groupBy ((==) `on` nameOf) (sortBy (comparing nameOf) xs) + , let merged = LegacyExeDependency (nameOf g) (mergeVersions (ordNub . filter (/= anyVersion) $ versionOf <$> gs)) + ] + where + mergeVersions :: [VersionRange] -> VersionRange + mergeVersions [] = anyVersion + mergeVersions (v : vs) = foldr intersectVersionRanges v vs + finalizeAndConfigurePackage :: ConfigFlags -> LBC.LocalBuildConfig From e8549726c60cd5a9e511857d1d6a7f7d73ef1d79 Mon Sep 17 00:00:00 2001 From: Phil de Joux Date: Sun, 19 Jan 2025 20:20:44 -0500 Subject: [PATCH 2/2] Show the number, change the wording --- Cabal/src/Distribution/Simple/Configure.hs | 17 +++++++++++++---- 1 file changed, 13 insertions(+), 4 deletions(-) diff --git a/Cabal/src/Distribution/Simple/Configure.hs b/Cabal/src/Distribution/Simple/Configure.hs index 48bd130c11c..679e5af4de2 100644 --- a/Cabal/src/Distribution/Simple/Configure.hs +++ b/Cabal/src/Distribution/Simple/Configure.hs @@ -176,7 +176,9 @@ import Text.PrettyPrint , char , colon , hsep + , int , nest + , parens , quotes , renderStyle , text @@ -898,10 +900,11 @@ configurePackage cfg lbc0 pkg_descr00 flags enabled comp platform programDb0 pac (merged, ds@(dup : _)) -> noticeDoc verbosity $ vcat - [ (text "The build tool" <+> quotes (text $ nameOf dup) <+> "has multiple versions specified") <> colon - , nest 2 $ vcat [char '-' <+> text (prettyShow $ versionOf d) | d <- ds] - , text "These versions have been combined as" <> colon - , nest 2 $ quotes (text $ prettyShow merged) + [ (text "As the build tool" <+> quotes (text $ nameOf dup) <+> "was specified more than once") <> colon + , nest 2 $ vcat [char '-' <+> versionOfDoc d | d <- ds] + , (text "We'll use the effective intersection of these" <+> int (length ds) <+> "version ranges") <> colon + , nest 2 $ char '-' <+> versionOfDoc merged + , text "Please specify build tool dependencies only once." ] programDb1 <- @@ -959,6 +962,12 @@ nameOf (LegacyExeDependency n _) = n versionOf :: LegacyExeDependency -> VersionRange versionOf (LegacyExeDependency _ v) = v +versionOfDoc :: LegacyExeDependency -> Doc +versionOfDoc (LegacyExeDependency _ v) = + if v == anyVersion + then text (prettyShow v) <+> parens (text "any version") + else text $ prettyShow v + -- | Any duplicates in the list has their version range merged by intersection. -- The second list has the build tool with its merged version range and its list -- of duplicates.