Skip to content

Commit 656d06b

Browse files
committed
Refactor CmdInstall
CmdInstall.installAction is ~300 lines long and full of nested scopes and ad-hoc logic. This change hopes to make it more readable and understandable. - Lift withProject and withoutProject out of installAction and split their relative concerns. E.g. not parsing URIs is installAction's concern not withProject's (which would just return a constant []). - Split an intermediate step into a separate function, resolveTargetSelectorsInProjectBaseContext. - Reuse withGlobalConfig and specFromPkgId (renamed from pidPackageSpecifiers). - Avoid trying withProject a second time in case no target is specified. - Fix a bug introduced in 802a326 where establishProjectBaseContext is called in a non-project setting. Also simplify its original implementation by moving the change into withProject rather than calling establishProjectBaseContext a second time. - Document the interaction between cabal v2-install and local configuration and add few comments.
1 parent 3d3622f commit 656d06b

File tree

9 files changed

+253
-217
lines changed

9 files changed

+253
-217
lines changed

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

Lines changed: 204 additions & 163 deletions
Large diffs are not rendered by default.

cabal-install/src/Distribution/Client/CmdInstall/ClientInstallTargetSelector.hs

Lines changed: 2 additions & 13 deletions
Original file line numberDiff line numberDiff line change
@@ -18,8 +18,6 @@ import Distribution.Compat.CharParsing (char, optional)
1818
import Distribution.Package
1919
import Distribution.Simple.LocalBuildInfo (ComponentName (CExeName))
2020
import Distribution.Simple.Utils (dieWithException)
21-
import Distribution.Solver.Types.PackageConstraint (PackageProperty (..))
22-
import Distribution.Version
2321

2422
data WithoutProjectTargetSelector
2523
= WoPackageId PackageId
@@ -57,15 +55,6 @@ woPackageTargets (WoURI _) =
5755
TargetAllPackages (Just ExeKind)
5856

5957
woPackageSpecifiers :: WithoutProjectTargetSelector -> Either URI (PackageSpecifier pkg)
60-
woPackageSpecifiers (WoPackageId pid) = Right (pidPackageSpecifiers pid)
61-
woPackageSpecifiers (WoPackageComponent pid _) = Right (pidPackageSpecifiers pid)
58+
woPackageSpecifiers (WoPackageId pid) = Right (mkNamedPackage pid)
59+
woPackageSpecifiers (WoPackageComponent pid _) = Right (mkNamedPackage pid)
6260
woPackageSpecifiers (WoURI uri) = Left uri
63-
64-
pidPackageSpecifiers :: PackageId -> PackageSpecifier pkg
65-
pidPackageSpecifiers pid
66-
| pkgVersion pid == nullVersion = NamedPackage (pkgName pid) []
67-
| otherwise =
68-
NamedPackage
69-
(pkgName pid)
70-
[ PackagePropertyVersion (thisVersion (pkgVersion pid))
71-
]

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

Lines changed: 6 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -32,6 +32,7 @@ import Distribution.Client.ProjectConfig
3232
, commandLineFlagsToProjectConfig
3333
, projectConfigConfigFile
3434
, projectConfigShared
35+
, withGlobalConfig
3536
, withProjectOrGlobalConfig
3637
)
3738
import Distribution.Client.ProjectFlags
@@ -219,7 +220,11 @@ sdistOptions showOrParseArgs =
219220

220221
sdistAction :: (ProjectFlags, SdistFlags) -> [String] -> GlobalFlags -> IO ()
221222
sdistAction (pf@ProjectFlags{..}, SdistFlags{..}) targetStrings globalFlags = do
222-
(baseCtx, distDirLayout) <- withProjectOrGlobalConfig verbosity flagIgnoreProject globalConfigFlag withProject withoutProject
223+
(baseCtx, distDirLayout) <-
224+
withProjectOrGlobalConfig
225+
flagIgnoreProject
226+
withProject
227+
(withGlobalConfig verbosity globalConfigFlag withoutProject)
223228

224229
let localPkgs = localPackages baseCtx
225230

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

Lines changed: 2 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -48,6 +48,7 @@ import Distribution.Client.ProjectConfig
4848
( ProjectConfig (..)
4949
, ProjectConfigShared (projectConfigConfigFile)
5050
, projectConfigWithSolverRepoContext
51+
, withGlobalConfig
5152
, withProjectOrGlobalConfig
5253
)
5354
import Distribution.Client.ProjectFlags
@@ -162,11 +163,9 @@ updateAction flags@NixStyleFlags{..} extraArgs globalFlags = do
162163

163164
projectConfig <-
164165
withProjectOrGlobalConfig
165-
verbosity
166166
ignoreProject
167-
globalConfigFlag
168167
(projectConfig <$> establishProjectBaseContext verbosity cliConfig OtherCommand)
169-
(\globalConfig -> return $ globalConfig <> cliConfig)
168+
(withGlobalConfig verbosity globalConfigFlag $ \globalConfig -> return $ globalConfig <> cliConfig)
170169

171170
projectConfigWithSolverRepoContext
172171
verbosity

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

Lines changed: 17 additions & 34 deletions
Original file line numberDiff line numberDiff line change
@@ -621,41 +621,34 @@ withGlobalConfig verbosity gcf with = do
621621
with globalConfig
622622

623623
withProjectOrGlobalConfig
624-
:: Verbosity
625-
-- ^ verbosity
626-
-> Flag Bool
624+
:: Flag Bool
627625
-- ^ whether to ignore local project (--ignore-project flag)
628-
-> Flag FilePath
629-
-- ^ @--cabal-config@
630626
-> IO a
631-
-- ^ with project
632-
-> (ProjectConfig -> IO a)
633-
-- ^ without project
627+
-- ^ continuation with project
634628
-> IO a
635-
withProjectOrGlobalConfig verbosity (Flag True) gcf _with without = do
636-
globalConfig <- runRebuild "" $ readGlobalConfig verbosity gcf
637-
without globalConfig
638-
withProjectOrGlobalConfig verbosity _ignorePrj gcf with without =
639-
withProjectOrGlobalConfig' verbosity gcf with without
629+
-- ^ continuation without project
630+
-> IO a
631+
withProjectOrGlobalConfig (Flag True) _with without = do
632+
without
633+
withProjectOrGlobalConfig _ignorePrj with without =
634+
withProjectOrGlobalConfig' with without
640635

641636
withProjectOrGlobalConfig'
642-
:: Verbosity
643-
-> Flag FilePath
637+
:: IO a
638+
-- ^ continuation with project
644639
-> IO a
645-
-> (ProjectConfig -> IO a)
640+
-- ^ continuation without project
646641
-> IO a
647-
withProjectOrGlobalConfig' verbosity globalConfigFlag with without = do
648-
globalConfig <- runRebuild "" $ readGlobalConfig verbosity globalConfigFlag
649-
642+
withProjectOrGlobalConfig' with without = do
650643
catch with $
651644
\case
652645
(BadPackageLocations prov locs)
653646
| prov == Set.singleton Implicit
654647
, let
655648
isGlobErr (BadLocGlobEmptyMatch _) = True
656649
isGlobErr _ = False
657-
, any isGlobErr locs ->
658-
without globalConfig
650+
, any isGlobErr locs -> do
651+
without
659652
err -> throwIO err
660653

661654
-- | Read all the config relevant for a project. This includes the project
@@ -956,7 +949,7 @@ renderBadPackageLocationMatch bplm = case bplm of
956949
++ "' contains multiple "
957950
++ ".cabal files (which is not currently supported)."
958951

959-
-- | Given the project config,
952+
-- | Determines the location of all packages mentioned in the project configuration.
960953
--
961954
-- Throws 'BadPackageLocations'.
962955
findProjectPackages
@@ -986,11 +979,7 @@ findProjectPackages
986979
findPackageLocation
987980
:: Bool
988981
-> String
989-
-> Rebuild
990-
( Either
991-
BadPackageLocation
992-
[ProjectPackageLocation]
993-
)
982+
-> Rebuild (Either BadPackageLocation [ProjectPackageLocation])
994983
findPackageLocation _required@True pkglocstr =
995984
-- strategy: try first as a file:// or http(s):// URL.
996985
-- then as a file glob (usually encompassing single file)
@@ -1011,13 +1000,7 @@ findProjectPackages
10111000
, checkIsFileGlobPackage
10121001
, checkIsSingleFilePackage
10131002
:: String
1014-
-> Rebuild
1015-
( Maybe
1016-
( Either
1017-
BadPackageLocation
1018-
[ProjectPackageLocation]
1019-
)
1020-
)
1003+
-> Rebuild (Maybe (Either BadPackageLocation [ProjectPackageLocation]))
10211004
checkIsUriPackage pkglocstr =
10221005
case parseAbsoluteURI pkglocstr of
10231006
Just

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

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -237,6 +237,9 @@ data ProjectBaseContext = ProjectBaseContext
237237
, cabalDirLayout :: CabalDirLayout
238238
, projectConfig :: ProjectConfig
239239
, localPackages :: [PackageSpecifier UnresolvedSourcePackage]
240+
-- ^ Note: these are all the packages mentioned in the project configuration.
241+
-- Whether or not they will be considered local to the project will be decided
242+
-- by `shouldBeLocal` in ProjectPlanning.
240243
, buildSettings :: BuildTimeSettings
241244
, currentCommand :: CurrentCommand
242245
, installedPackages :: Maybe InstalledPackageIndex

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

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -409,6 +409,8 @@ rebuildProjectConfig
409409
-- Look for all the cabal packages in the project
410410
-- some of which may be local src dirs, tarballs etc
411411
--
412+
-- NOTE: These are all packages mentioned in the project configuration.
413+
-- Whether or not they will be considered local to the project will be decided by `shouldBeLocal`.
412414
phaseReadLocalPackages
413415
:: ProjectConfig
414416
-> Rebuild [PackageSpecifier UnresolvedSourcePackage]

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

Lines changed: 5 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -292,7 +292,11 @@ withContextAndSelectors
292292
-> IO b
293293
withContextAndSelectors noTargets kind flags@NixStyleFlags{..} targetStrings globalFlags cmd act =
294294
withTemporaryTempDirectory $ \mkTmpDir -> do
295-
(tc, ctx) <- withProjectOrGlobalConfig verbosity ignoreProject globalConfigFlag withProject (withoutProject mkTmpDir)
295+
(tc, ctx) <-
296+
withProjectOrGlobalConfig
297+
ignoreProject
298+
withProject
299+
(withGlobalConfig verbosity globalConfigFlag $ withoutProject mkTmpDir)
296300

297301
(tc', ctx', sels) <- case targetStrings of
298302
-- Only script targets may contain spaces and or end with ':'.

cabal-install/src/Distribution/Client/Types/PackageSpecifier.hs

Lines changed: 12 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -5,14 +5,15 @@ module Distribution.Client.Types.PackageSpecifier
55
( PackageSpecifier (..)
66
, pkgSpecifierTarget
77
, pkgSpecifierConstraints
8+
, mkNamedPackage
89
) where
910

1011
import Distribution.Client.Compat.Prelude
1112
import Prelude ()
1213

13-
import Distribution.Package (Package (..), packageName, packageVersion)
14+
import Distribution.Package (Package (..), PackageIdentifier (..), packageName, packageVersion)
1415
import Distribution.Types.PackageName (PackageName)
15-
import Distribution.Version (thisVersion)
16+
import Distribution.Version (nullVersion, thisVersion)
1617

1718
import Distribution.Solver.Types.ConstraintSource
1819
import Distribution.Solver.Types.LabeledPackageConstraint
@@ -53,3 +54,12 @@ pkgSpecifierConstraints (SpecificSourcePackage pkg) =
5354
PackageConstraint
5455
(ScopeTarget $ packageName pkg)
5556
(PackagePropertyVersion $ thisVersion (packageVersion pkg))
57+
58+
mkNamedPackage :: PackageIdentifier -> PackageSpecifier pkg
59+
mkNamedPackage pkgId =
60+
NamedPackage
61+
(pkgName pkgId)
62+
( if pkgVersion pkgId == nullVersion
63+
then []
64+
else [PackagePropertyVersion (thisVersion (pkgVersion pkgId))]
65+
)

0 commit comments

Comments
 (0)