Skip to content

Commit

Permalink
Combine duplicate build tools
Browse files Browse the repository at this point in the history
- report the duplicate versions
- intersect the version ranges
  • Loading branch information
philderbeast committed Jan 20, 2025
1 parent 54d364d commit b581165
Showing 1 changed file with 42 additions and 2 deletions.
44 changes: 42 additions & 2 deletions Cabal/src/Distribution/Simple/Configure.hs
Original file line number Diff line number Diff line change
@@ -1,5 +1,6 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RankNTypes #-}
Expand Down Expand Up @@ -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
, (\\)
)
Expand Down Expand Up @@ -172,10 +174,13 @@ import qualified System.Info
import Text.PrettyPrint
( Doc
, char
, colon
, hsep
, nest
, quotes
, renderStyle
, text
, vcat
, ($+$)
)

Expand Down Expand Up @@ -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 =
[]
Expand Down Expand Up @@ -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
Expand Down Expand Up @@ -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
Expand Down

0 comments on commit b581165

Please sign in to comment.