Skip to content

Commit 7b92cdc

Browse files
committed
Implement v2-gen-bounds function
This commit implements project-aware functionality for the `cabal gen-bounds` command, allowing it to work correctly in multi-package projects. Previously, running `gen-bounds` from within a package directory that depends on another local package would fail because it couldn't find the local dependency. The implementation follows the same pattern as other v2 commands, creating a full project context that knows about all packages defined in the cabal.project file. This allows `gen-bounds` to properly analyze dependencies between local packages and suggest appropriate bounds. ``` cabal gen-bounds <TARGET> ``` Fixes #7504 #8654 #9752 #5932
1 parent d4d92e9 commit 7b92cdc

File tree

18 files changed

+499
-20
lines changed

18 files changed

+499
-20
lines changed

cabal-install/cabal-install.cabal

+1
Original file line numberDiff line numberDiff line change
@@ -118,6 +118,7 @@ library
118118
Distribution.Client.CmdTarget
119119
Distribution.Client.CmdTest
120120
Distribution.Client.CmdUpdate
121+
Distribution.Client.CmdGenBounds
121122
Distribution.Client.Compat.Directory
122123
Distribution.Client.Compat.ExecutablePath
123124
Distribution.Client.Compat.Orphans
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,246 @@
1+
{-# LANGUAGE NamedFieldPuns #-}
2+
3+
module Distribution.Client.CmdGenBounds
4+
( genBounds
5+
, genBoundsCommand
6+
, genBoundsAction
7+
, GenBoundsFlags (..)
8+
, defaultGenBoundsFlags
9+
) where
10+
11+
import Distribution.Client.Compat.Prelude
12+
import Prelude ()
13+
14+
import qualified Data.Map as Map
15+
16+
import Prelude ()
17+
18+
import Distribution.Client.Errors
19+
20+
import Distribution.Client.ProjectPlanning hiding (pruneInstallPlanToTargets)
21+
import Distribution.Client.ProjectPlanning.Types
22+
import Distribution.Client.Types.ConfiguredId (confInstId)
23+
import Distribution.Client.Utils hiding (pvpize)
24+
import Distribution.InstalledPackageInfo (InstalledPackageInfo, installedComponentId)
25+
import Distribution.Package
26+
import Distribution.PackageDescription
27+
import Distribution.Simple.Utils
28+
import Distribution.Version
29+
30+
import Distribution.Client.Setup (CommonSetupFlags (..), ConfigFlags (..), GlobalFlags (..))
31+
32+
-- Project orchestration imports
33+
34+
import Distribution.Client.CmdErrorMessages
35+
import Distribution.Client.GenBounds
36+
import qualified Distribution.Client.InstallPlan as InstallPlan
37+
import Distribution.Client.NixStyleOptions
38+
import Distribution.Client.ProjectFlags
39+
import Distribution.Client.ProjectOrchestration
40+
import Distribution.Client.ScriptUtils
41+
import Distribution.Client.TargetProblem
42+
import Distribution.Simple.Command
43+
import Distribution.Simple.Flag
44+
import Distribution.Types.Component
45+
import Distribution.Verbosity
46+
47+
-- | The data type for gen-bounds command flags
48+
data GenBoundsFlags = GenBoundsFlags {}
49+
50+
-- | Default values for the gen-bounds flags
51+
defaultGenBoundsFlags :: GenBoundsFlags
52+
defaultGenBoundsFlags = GenBoundsFlags{}
53+
54+
-- | The @gen-bounds@ command definition
55+
genBoundsCommand :: CommandUI (NixStyleFlags GenBoundsFlags)
56+
genBoundsCommand =
57+
CommandUI
58+
{ commandName = "v2-gen-bounds"
59+
, commandSynopsis = "Generate dependency bounds for packages in the project."
60+
, commandUsage = usageAlternatives "v2-gen-bounds" ["[TARGETS] [FLAGS]"]
61+
, commandDescription = Just $ \_ ->
62+
"Generate PVP-compliant dependency bounds for packages in the project."
63+
, commandNotes = Just $ \pname ->
64+
"Examples:\n"
65+
++ " "
66+
++ pname
67+
++ " v2-gen-bounds\n"
68+
++ " Generate bounds for the package in the current directory "
69+
++ "or all packages in the project\n"
70+
++ " "
71+
++ pname
72+
++ " v2-gen-bounds pkgname\n"
73+
++ " Generate bounds for the package named pkgname in the project\n"
74+
++ " "
75+
++ pname
76+
++ " v2-gen-bounds ./pkgfoo\n"
77+
++ " Generate bounds for the package in the ./pkgfoo directory\n"
78+
, commandDefaultFlags = defaultNixStyleFlags defaultGenBoundsFlags
79+
, commandOptions =
80+
removeIgnoreProjectOption
81+
. nixStyleOptions (const [])
82+
}
83+
84+
-- | The action for the @gen-bounds@ command when used in a project context.
85+
genBoundsAction :: NixStyleFlags GenBoundsFlags -> [String] -> GlobalFlags -> IO ()
86+
genBoundsAction flags targetStrings globalFlags =
87+
withContextAndSelectors RejectNoTargets Nothing flags targetStrings globalFlags OtherCommand $ \targetCtx ctx targetSelectors -> do
88+
let verbosity = fromFlagOrDefault normal (setupVerbosity $ configCommonFlags $ configFlags flags)
89+
90+
baseCtx <- case targetCtx of
91+
ProjectContext -> return ctx
92+
GlobalContext -> return ctx
93+
ScriptContext path _ ->
94+
dieWithException verbosity $
95+
GenBoundsDoesNotSupportScript path
96+
97+
let ProjectBaseContext{distDirLayout, cabalDirLayout, projectConfig, localPackages} = baseCtx
98+
99+
-- Step 1: Create the install plan for the project.
100+
(_, elaboratedPlan, _, _, _) <-
101+
rebuildInstallPlan
102+
verbosity
103+
distDirLayout
104+
cabalDirLayout
105+
projectConfig
106+
localPackages
107+
Nothing
108+
109+
-- Step 2: Resolve the targets for the gen-bounds command.
110+
targets <-
111+
either (reportGenBoundsTargetProblems verbosity) return $
112+
resolveTargets
113+
selectPackageTargets
114+
selectComponentTarget
115+
elaboratedPlan
116+
Nothing
117+
targetSelectors
118+
119+
-- Step 3: Prune the install plan to the targets.
120+
let elaboratedPlan' =
121+
pruneInstallPlanToTargets
122+
TargetActionBuild
123+
targets
124+
elaboratedPlan
125+
126+
let
127+
-- Step 4a: Find the local packages from the install plan. These are the
128+
-- candidates for which we will generate bounds.
129+
localPkgs :: [ElaboratedConfiguredPackage]
130+
localPkgs = mapMaybe (InstallPlan.foldPlanPackage (const Nothing) (\p -> Just p)) (InstallPlan.toList elaboratedPlan')
131+
132+
-- Step 4b: Extract which versions we chose for each package from the pruned install plan.
133+
pkgVersionMap :: Map.Map ComponentId PackageIdentifier
134+
pkgVersionMap = Map.fromList (map (InstallPlan.foldPlanPackage externalVersion localVersion) (InstallPlan.toList elaboratedPlan'))
135+
136+
externalVersion :: InstalledPackageInfo -> (ComponentId, PackageIdentifier)
137+
externalVersion pkg = (installedComponentId pkg, packageId pkg)
138+
139+
localVersion :: ElaboratedConfiguredPackage -> (ComponentId, PackageIdentifier)
140+
localVersion pkg = (elabComponentId pkg, packageId pkg)
141+
142+
let genBoundsActionForPkg :: ElaboratedConfiguredPackage -> [IO ()]
143+
genBoundsActionForPkg pkg =
144+
-- Step 5: Match up the user specified targets with the local packages.
145+
case Map.lookup (installedUnitId pkg) targets of
146+
Nothing -> []
147+
Just tgts ->
148+
map (\(tgt, _) -> processBuildInfo verbosity tgt pkg pkgVersionMap) tgts
149+
150+
-- Process each package to find the ones needing bounds
151+
let boundsActions = concatMap genBoundsActionForPkg localPkgs
152+
153+
case boundsActions of
154+
[] -> notice verbosity "All bounds up-to-date"
155+
_ -> do
156+
notice verbosity boundsNeededMsg
157+
sequence_ (intersperse (putStrLn "") boundsActions)
158+
159+
-- | Process a single BuildInfo to identify and report missing upper bounds
160+
processBuildInfo
161+
:: Verbosity
162+
-> ComponentTarget
163+
-> ElaboratedConfiguredPackage
164+
-> Map.Map ComponentId PackageIdentifier
165+
-> IO ()
166+
processBuildInfo verbosity tgt pkg pkgVersionMap = do
167+
let pd = elabPkgDescription pkg
168+
-- Extract the build-depends for the right part of the cabal file.
169+
bi = buildInfoForTarget pd tgt
170+
171+
-- We need to generate bounds if
172+
-- \* the dependency does not have an upper bound
173+
-- \* the dependency is not the same package as the one we are processing
174+
boundFilter dep =
175+
(not (hasUpperBound (depVerRange dep)))
176+
&& packageName pd /= depPkgName dep
177+
178+
-- The dependencies that need bounds.
179+
needBounds = map depPkgName $ filter boundFilter $ targetBuildDepends bi
180+
181+
if null needBounds
182+
then
183+
notice
184+
verbosity
185+
("Congratulations, all dependencies for " ++ prettyShow (packageName pd) ++ ":" ++ showComponentTarget (packageId pkg) tgt ++ " have upper bounds!")
186+
else do
187+
notice verbosity $
188+
"For component " ++ prettyShow (packageName pd) ++ ":" ++ showComponentTarget (packageId pkg) tgt ++ ":"
189+
190+
-- All the things we depend on.
191+
let componentDeps = elabLibDependencies pkg
192+
-- Match these up to package names, this is a list of Package name to versions.
193+
-- Now just match that up with what the user wrote in the build-depends section.
194+
depsWithVersions = mapMaybe (\cid -> Map.lookup (confInstId $ fst cid) pkgVersionMap) componentDeps
195+
isNeeded = hasElem needBounds . packageName
196+
thePkgs = filter isNeeded depsWithVersions
197+
198+
let padTo = maximum $ map (length . unPackageName . packageName) thePkgs
199+
200+
traverse_ (notice verbosity . (++ ",") . showBounds padTo) thePkgs
201+
202+
buildInfoForTarget :: PackageDescription -> ComponentTarget -> BuildInfo
203+
buildInfoForTarget pd (ComponentTarget cname _) = componentBuildInfo $ getComponent pd cname
204+
205+
-- | This defines what a 'TargetSelector' means for the @gen-bounds@ command.
206+
-- Copy of selectPackageTargets from CmdBuild.hs
207+
selectPackageTargets
208+
:: TargetSelector
209+
-> [AvailableTarget k]
210+
-> Either TargetProblem' [k]
211+
selectPackageTargets targetSelector targets
212+
-- If there are any buildable targets then we select those
213+
| not (null targetsBuildable) =
214+
Right targetsBuildable
215+
-- If there are targets but none are buildable then we report those
216+
| not (null targets) =
217+
Left (TargetProblemNoneEnabled targetSelector targets')
218+
-- If there are no targets at all then we report that
219+
| otherwise =
220+
Left (TargetProblemNoTargets targetSelector)
221+
where
222+
targets' = forgetTargetsDetail targets
223+
targetsBuildable =
224+
selectBuildableTargetsWith
225+
(buildable targetSelector)
226+
targets
227+
228+
-- When there's a target filter like "pkg:tests" then we do select tests,
229+
-- but if it's just a target like "pkg" then we don't build tests unless
230+
-- they are requested by default (i.e. by using --enable-tests)
231+
buildable (TargetPackage _ _ Nothing) TargetNotRequestedByDefault = False
232+
buildable (TargetAllPackages Nothing) TargetNotRequestedByDefault = False
233+
buildable _ _ = True
234+
235+
-- | For a 'TargetComponent' 'TargetSelector', check if the component can be
236+
-- selected. Copy of selectComponentTarget from CmdBuild.hs
237+
selectComponentTarget
238+
:: SubComponentTarget
239+
-> AvailableTarget k
240+
-> Either TargetProblem' k
241+
selectComponentTarget = selectComponentTargetBasic
242+
243+
-- | Report target problems for gen-bounds command
244+
reportGenBoundsTargetProblems :: Verbosity -> [TargetProblem'] -> IO a
245+
reportGenBoundsTargetProblems verbosity problems =
246+
reportTargetProblems verbosity "gen-bounds" problems

cabal-install/src/Distribution/Client/Errors.hs

+4
Original file line numberDiff line numberDiff line change
@@ -186,6 +186,7 @@ data CabalInstallException
186186
| MissingPackageList Repo.RemoteRepo
187187
| CmdPathAcceptsNoTargets
188188
| CmdPathCommandDoesn'tSupportDryRun
189+
| GenBoundsDoesNotSupportScript FilePath
189190
deriving (Show)
190191

191192
exceptionCodeCabalInstall :: CabalInstallException -> Int
@@ -338,6 +339,7 @@ exceptionCodeCabalInstall e = case e of
338339
MissingPackageList{} -> 7160
339340
CmdPathAcceptsNoTargets{} -> 7161
340341
CmdPathCommandDoesn'tSupportDryRun -> 7163
342+
GenBoundsDoesNotSupportScript{} -> 7164
341343

342344
exceptionMessageCabalInstall :: CabalInstallException -> String
343345
exceptionMessageCabalInstall e = case e of
@@ -860,6 +862,8 @@ exceptionMessageCabalInstall e = case e of
860862
"The 'path' command accepts no target arguments."
861863
CmdPathCommandDoesn'tSupportDryRun ->
862864
"The 'path' command doesn't support the flag '--dry-run'."
865+
GenBoundsDoesNotSupportScript{} ->
866+
"The 'gen-bounds' command does not support script targets."
863867

864868
instance Exception (VerboseException CabalInstallException) where
865869
displayException :: VerboseException CabalInstallException -> [Char]

cabal-install/src/Distribution/Client/GenBounds.hs

+2
Original file line numberDiff line numberDiff line change
@@ -10,6 +10,8 @@
1010
-- The cabal gen-bounds command for generating PVP-compliant version bounds.
1111
module Distribution.Client.GenBounds
1212
( genBounds
13+
, boundsNeededMsg
14+
, showBounds
1315
) where
1416

1517
import Distribution.Client.Compat.Prelude

cabal-install/src/Distribution/Client/Main.hs

+3-1
Original file line numberDiff line numberDiff line change
@@ -120,6 +120,7 @@ import qualified Distribution.Client.CmdClean as CmdClean
120120
import qualified Distribution.Client.CmdConfigure as CmdConfigure
121121
import qualified Distribution.Client.CmdExec as CmdExec
122122
import qualified Distribution.Client.CmdFreeze as CmdFreeze
123+
import qualified Distribution.Client.CmdGenBounds as CmdGenBounds
123124
import qualified Distribution.Client.CmdHaddock as CmdHaddock
124125
import qualified Distribution.Client.CmdHaddockProject as CmdHaddockProject
125126
import qualified Distribution.Client.CmdInstall as CmdInstall
@@ -436,7 +437,6 @@ mainWorker args = do
436437
, regularCmd initCommand initAction
437438
, regularCmd userConfigCommand userConfigAction
438439
, regularCmd CmdPath.pathCommand CmdPath.pathAction
439-
, regularCmd genBoundsCommand genBoundsAction
440440
, regularCmd CmdOutdated.outdatedCommand CmdOutdated.outdatedAction
441441
, wrapperCmd hscolourCommand hscolourCommonFlags
442442
, hiddenCmd formatCommand formatAction
@@ -462,7 +462,9 @@ mainWorker args = do
462462
, newCmd CmdClean.cleanCommand CmdClean.cleanAction
463463
, newCmd CmdSdist.sdistCommand CmdSdist.sdistAction
464464
, newCmd CmdTarget.targetCommand CmdTarget.targetAction
465+
, newCmd CmdGenBounds.genBoundsCommand CmdGenBounds.genBoundsAction
465466
, legacyCmd configureExCommand configureAction
467+
, legacyCmd genBoundsCommand genBoundsAction
466468
, legacyCmd buildCommand buildAction
467469
, legacyCmd replCommand replAction
468470
, legacyCmd freezeCommand freezeAction
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,17 @@
11
# cabal gen-bounds
22
Resolving dependencies...
3-
Congratulations, all your dependencies have upper bounds!
3+
4+
The following packages need bounds and here is a suggested starting point.
5+
You can copy and paste this into the build-depends section in your .cabal
6+
file and it should work (with the appropriate removal of commas).
7+
8+
Note that version bounds are a statement that you've successfully built and
9+
tested your package and expect it to work with any of the specified package
10+
versions (PROVIDED that those packages continue to conform with the PVP).
11+
Therefore, the version bounds generated here are the most conservative
12+
based on the versions that you are currently building with. If you know
13+
your package will work with versions outside the ranges generated here,
14+
feel free to widen them.
15+
16+
Congratulations, all dependencies for pkg:exe:exec have upper bounds!
17+
Congratulations, all dependencies for pkg:lib:lib have upper bounds!
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,25 @@
1+
# cabal gen-bounds
2+
Configuration is affected by the following files:
3+
- cabal.project
4+
Resolving dependencies...
5+
6+
The following packages need bounds and here is a suggested starting point.
7+
You can copy and paste this into the build-depends section in your .cabal
8+
file and it should work (with the appropriate removal of commas).
9+
10+
Note that version bounds are a statement that you've successfully built and
11+
tested your package and expect it to work with any of the specified package
12+
versions (PROVIDED that those packages continue to conform with the PVP).
13+
Therefore, the version bounds generated here are the most conservative
14+
based on the versions that you are currently building with. If you know
15+
your package will work with versions outside the ranges generated here,
16+
feel free to widen them.
17+
18+
For component package-a:lib:package-a:
19+
text >= 2.1.1 && < 2.2,
20+
For component package-b:lib:package-b:
21+
base >= 4.20.0 && < 4.21,
22+
package-a >= 0.1.0 && < 0.2,
23+
For component package-b:exe:package-b:
24+
base >= 4.20.0 && < 4.21,
25+
package-a >= 0.1.0 && < 0.2,
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,2 @@
1+
packages: package-a
2+
package-b
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,6 @@
1+
import System.Directory (setCurrentDirectory)
2+
import Test.Cabal.Prelude
3+
4+
main = cabalTest $ do
5+
cabal "gen-bounds" ["all"]
6+

0 commit comments

Comments
 (0)