Skip to content

Commit 04c7f02

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 04c7f02

File tree

18 files changed

+497
-20
lines changed

18 files changed

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

0 commit comments

Comments
 (0)