Skip to content

Commit

Permalink
Refactor CmdInstall
Browse files Browse the repository at this point in the history
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.
  • Loading branch information
andreabedini committed Feb 16, 2024
1 parent bd5bafc commit 4d55140
Show file tree
Hide file tree
Showing 9 changed files with 253 additions and 217 deletions.
367 changes: 204 additions & 163 deletions cabal-install/src/Distribution/Client/CmdInstall.hs

Large diffs are not rendered by default.

Original file line number Diff line number Diff line change
Expand Up @@ -18,8 +18,6 @@ import Distribution.Compat.CharParsing (char, optional)
import Distribution.Package
import Distribution.Simple.LocalBuildInfo (ComponentName (CExeName))
import Distribution.Simple.Utils (dieWithException)
import Distribution.Solver.Types.PackageConstraint (PackageProperty (..))
import Distribution.Version

data WithoutProjectTargetSelector
= WoPackageId PackageId
Expand Down Expand Up @@ -57,15 +55,6 @@ woPackageTargets (WoURI _) =
TargetAllPackages (Just ExeKind)

woPackageSpecifiers :: WithoutProjectTargetSelector -> Either URI (PackageSpecifier pkg)
woPackageSpecifiers (WoPackageId pid) = Right (pidPackageSpecifiers pid)
woPackageSpecifiers (WoPackageComponent pid _) = Right (pidPackageSpecifiers pid)
woPackageSpecifiers (WoPackageId pid) = Right (mkNamedPackage pid)
woPackageSpecifiers (WoPackageComponent pid _) = Right (mkNamedPackage pid)
woPackageSpecifiers (WoURI uri) = Left uri

pidPackageSpecifiers :: PackageId -> PackageSpecifier pkg
pidPackageSpecifiers pid
| pkgVersion pid == nullVersion = NamedPackage (pkgName pid) []
| otherwise =
NamedPackage
(pkgName pid)
[ PackagePropertyVersion (thisVersion (pkgVersion pid))
]
7 changes: 6 additions & 1 deletion cabal-install/src/Distribution/Client/CmdSdist.hs
Original file line number Diff line number Diff line change
Expand Up @@ -32,6 +32,7 @@ import Distribution.Client.ProjectConfig
, commandLineFlagsToProjectConfig
, projectConfigConfigFile
, projectConfigShared
, withGlobalConfig
, withProjectOrGlobalConfig
)
import Distribution.Client.ProjectFlags
Expand Down Expand Up @@ -219,7 +220,11 @@ sdistOptions showOrParseArgs =

sdistAction :: (ProjectFlags, SdistFlags) -> [String] -> GlobalFlags -> IO ()
sdistAction (pf@ProjectFlags{..}, SdistFlags{..}) targetStrings globalFlags = do
(baseCtx, distDirLayout) <- withProjectOrGlobalConfig verbosity flagIgnoreProject globalConfigFlag withProject withoutProject
(baseCtx, distDirLayout) <-
withProjectOrGlobalConfig
flagIgnoreProject
withProject
(withGlobalConfig verbosity globalConfigFlag withoutProject)

let localPkgs = localPackages baseCtx

Expand Down
5 changes: 2 additions & 3 deletions cabal-install/src/Distribution/Client/CmdUpdate.hs
Original file line number Diff line number Diff line change
Expand Up @@ -48,6 +48,7 @@ import Distribution.Client.ProjectConfig
( ProjectConfig (..)
, ProjectConfigShared (projectConfigConfigFile)
, projectConfigWithSolverRepoContext
, withGlobalConfig
, withProjectOrGlobalConfig
)
import Distribution.Client.ProjectFlags
Expand Down Expand Up @@ -162,11 +163,9 @@ updateAction flags@NixStyleFlags{..} extraArgs globalFlags = do

projectConfig <-
withProjectOrGlobalConfig
verbosity
ignoreProject
globalConfigFlag
(projectConfig <$> establishProjectBaseContext verbosity cliConfig OtherCommand)
(\globalConfig -> return $ globalConfig <> cliConfig)
(withGlobalConfig verbosity globalConfigFlag $ \globalConfig -> return $ globalConfig <> cliConfig)

projectConfigWithSolverRepoContext
verbosity
Expand Down
51 changes: 17 additions & 34 deletions cabal-install/src/Distribution/Client/ProjectConfig.hs
Original file line number Diff line number Diff line change
Expand Up @@ -621,41 +621,34 @@ withGlobalConfig verbosity gcf with = do
with globalConfig

withProjectOrGlobalConfig
:: Verbosity
-- ^ verbosity
-> Flag Bool
:: Flag Bool
-- ^ whether to ignore local project (--ignore-project flag)
-> Flag FilePath
-- ^ @--cabal-config@
-> IO a
-- ^ with project
-> (ProjectConfig -> IO a)
-- ^ without project
-- ^ continuation with project
-> IO a
withProjectOrGlobalConfig verbosity (Flag True) gcf _with without = do
globalConfig <- runRebuild "" $ readGlobalConfig verbosity gcf
without globalConfig
withProjectOrGlobalConfig verbosity _ignorePrj gcf with without =
withProjectOrGlobalConfig' verbosity gcf with without
-- ^ continuation without project
-> IO a
withProjectOrGlobalConfig (Flag True) _with without = do
without
withProjectOrGlobalConfig _ignorePrj with without =
withProjectOrGlobalConfig' with without

withProjectOrGlobalConfig'
:: Verbosity
-> Flag FilePath
:: IO a
-- ^ continuation with project
-> IO a
-> (ProjectConfig -> IO a)
-- ^ continuation without project
-> IO a
withProjectOrGlobalConfig' verbosity globalConfigFlag with without = do
globalConfig <- runRebuild "" $ readGlobalConfig verbosity globalConfigFlag

withProjectOrGlobalConfig' with without = do
catch with $
\case
(BadPackageLocations prov locs)
| prov == Set.singleton Implicit
, let
isGlobErr (BadLocGlobEmptyMatch _) = True
isGlobErr _ = False
, any isGlobErr locs ->
without globalConfig
, any isGlobErr locs -> do
without
err -> throwIO err

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

-- | Given the project config,
-- | Determines the location of all packages mentioned in the project configuration.
--
-- Throws 'BadPackageLocations'.
findProjectPackages
Expand Down Expand Up @@ -986,11 +979,7 @@ findProjectPackages
findPackageLocation
:: Bool
-> String
-> Rebuild
( Either
BadPackageLocation
[ProjectPackageLocation]
)
-> Rebuild (Either BadPackageLocation [ProjectPackageLocation])
findPackageLocation _required@True pkglocstr =
-- strategy: try first as a file:// or http(s):// URL.
-- then as a file glob (usually encompassing single file)
Expand All @@ -1011,13 +1000,7 @@ findProjectPackages
, checkIsFileGlobPackage
, checkIsSingleFilePackage
:: String
-> Rebuild
( Maybe
( Either
BadPackageLocation
[ProjectPackageLocation]
)
)
-> Rebuild (Maybe (Either BadPackageLocation [ProjectPackageLocation]))
checkIsUriPackage pkglocstr =
case parseAbsoluteURI pkglocstr of
Just
Expand Down
3 changes: 3 additions & 0 deletions cabal-install/src/Distribution/Client/ProjectOrchestration.hs
Original file line number Diff line number Diff line change
Expand Up @@ -237,6 +237,9 @@ data ProjectBaseContext = ProjectBaseContext
, cabalDirLayout :: CabalDirLayout
, projectConfig :: ProjectConfig
, localPackages :: [PackageSpecifier UnresolvedSourcePackage]
-- ^ Note: these are all the packages mentioned in the project configuration.
-- Whether or not they will be considered local to the project will be decided
-- by `shouldBeLocal` in ProjectPlanning.
, buildSettings :: BuildTimeSettings
, currentCommand :: CurrentCommand
, installedPackages :: Maybe InstalledPackageIndex
Expand Down
2 changes: 2 additions & 0 deletions cabal-install/src/Distribution/Client/ProjectPlanning.hs
Original file line number Diff line number Diff line change
Expand Up @@ -409,6 +409,8 @@ rebuildProjectConfig
-- Look for all the cabal packages in the project
-- some of which may be local src dirs, tarballs etc
--
-- NOTE: These are all packages mentioned in the project configuration.
-- Whether or not they will be considered local to the project will be decided by `shouldBeLocal`.
phaseReadLocalPackages
:: ProjectConfig
-> Rebuild [PackageSpecifier UnresolvedSourcePackage]
Expand Down
6 changes: 5 additions & 1 deletion cabal-install/src/Distribution/Client/ScriptUtils.hs
Original file line number Diff line number Diff line change
Expand Up @@ -292,7 +292,11 @@ withContextAndSelectors
-> IO b
withContextAndSelectors noTargets kind flags@NixStyleFlags{..} targetStrings globalFlags cmd act =
withTemporaryTempDirectory $ \mkTmpDir -> do
(tc, ctx) <- withProjectOrGlobalConfig verbosity ignoreProject globalConfigFlag withProject (withoutProject mkTmpDir)
(tc, ctx) <-
withProjectOrGlobalConfig
ignoreProject
withProject
(withGlobalConfig verbosity globalConfigFlag $ withoutProject mkTmpDir)

(tc', ctx', sels) <- case targetStrings of
-- Only script targets may contain spaces and or end with ':'.
Expand Down
14 changes: 12 additions & 2 deletions cabal-install/src/Distribution/Client/Types/PackageSpecifier.hs
Original file line number Diff line number Diff line change
Expand Up @@ -5,14 +5,15 @@ module Distribution.Client.Types.PackageSpecifier
( PackageSpecifier (..)
, pkgSpecifierTarget
, pkgSpecifierConstraints
, mkNamedPackage
) where

import Distribution.Client.Compat.Prelude
import Prelude ()

import Distribution.Package (Package (..), packageName, packageVersion)
import Distribution.Package (Package (..), PackageIdentifier (..), packageName, packageVersion)
import Distribution.Types.PackageName (PackageName)
import Distribution.Version (thisVersion)
import Distribution.Version (nullVersion, thisVersion)

import Distribution.Solver.Types.ConstraintSource
import Distribution.Solver.Types.LabeledPackageConstraint
Expand Down Expand Up @@ -53,3 +54,12 @@ pkgSpecifierConstraints (SpecificSourcePackage pkg) =
PackageConstraint
(ScopeTarget $ packageName pkg)
(PackagePropertyVersion $ thisVersion (packageVersion pkg))

mkNamedPackage :: PackageIdentifier -> PackageSpecifier pkg
mkNamedPackage pkgId =
NamedPackage
(pkgName pkgId)
( if pkgVersion pkgId == nullVersion
then []
else [PackagePropertyVersion (thisVersion (pkgVersion pkgId))]
)

0 comments on commit 4d55140

Please sign in to comment.