Skip to content

Commit c3a9dd7

Browse files
authored
Merge pull request #10254 from alt-romes/wip/romes/cabal-shallow-mr
Shallow and concurrent git clones
2 parents 7ab3a5e + c89ab54 commit c3a9dd7

File tree

12 files changed

+205
-78
lines changed

12 files changed

+205
-78
lines changed

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

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -467,6 +467,7 @@ installAction flags@NixStyleFlags{extraFlags, configFlags, installFlags, project
467467
fetchAndReadSourcePackages
468468
verbosity
469469
distDirLayout
470+
compiler
470471
(projectConfigShared config)
471472
(projectConfigBuildOnly config)
472473
[ProjectPackageRemoteTarball uri | uri <- uris]

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

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -142,6 +142,7 @@ import Distribution.Solver.Types.PkgConfigDb
142142
import Distribution.Solver.Types.Settings
143143
import Distribution.Solver.Types.SourcePackage as SourcePackage
144144

145+
import Distribution.Client.ProjectConfig
145146
import Distribution.Client.Utils
146147
( MergeResult (..)
147148
, ProgressPhase (..)
@@ -1443,7 +1444,7 @@ performInstallations
14431444
if parallelInstall
14441445
then newParallelJobControl numJobs
14451446
else newSerialJobControl
1446-
fetchLimit <- newJobLimit (min numJobs numFetchJobs)
1447+
fetchLimit <- newJobLimit (min numJobs maxNumFetchJobs)
14471448
installLock <- newLock -- serialise installation
14481449
cacheLock <- newLock -- serialise access to setup exe cache
14491450
executeInstallPlan
@@ -1486,7 +1487,6 @@ performInstallations
14861487
cinfo = compilerInfo comp
14871488

14881489
numJobs = determineNumJobs (installNumJobs installFlags)
1489-
numFetchJobs = 2
14901490
parallelInstall = numJobs >= 2
14911491
keepGoing = fromFlag (installKeepGoing installFlags)
14921492
distPref =

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

Lines changed: 44 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -31,6 +31,11 @@ module Distribution.Client.JobControl
3131
, Lock
3232
, newLock
3333
, criticalSection
34+
35+
-- * Higher level utils
36+
, newJobControlFromParStrat
37+
, withJobControl
38+
, mapConcurrentWithJobs
3439
) where
3540

3641
import Distribution.Client.Compat.Prelude
@@ -40,11 +45,14 @@ import Control.Concurrent (forkIO, forkIOWithUnmask, threadDelay)
4045
import Control.Concurrent.MVar
4146
import Control.Concurrent.STM (STM, TVar, atomically, modifyTVar', newTVarIO, readTVar)
4247
import Control.Concurrent.STM.TChan
43-
import Control.Exception (bracket_, mask_, try)
48+
import Control.Exception (bracket, bracket_, mask_, try)
4449
import Control.Monad (forever, replicateM_)
4550
import Distribution.Client.Compat.Semaphore
51+
import Distribution.Client.Utils (numberOfProcessors)
4652
import Distribution.Compat.Stack
53+
import Distribution.Simple.Compiler
4754
import Distribution.Simple.Utils
55+
import Distribution.Types.ParStrat
4856
import System.Semaphore
4957

5058
-- | A simple concurrency abstraction. Jobs can be spawned and can complete
@@ -262,3 +270,38 @@ newLock = fmap Lock $ newMVar ()
262270

263271
criticalSection :: Lock -> IO a -> IO a
264272
criticalSection (Lock lck) act = bracket_ (takeMVar lck) (putMVar lck ()) act
273+
274+
--------------------------------------------------------------------------------
275+
-- More high level utils
276+
--------------------------------------------------------------------------------
277+
278+
newJobControlFromParStrat
279+
:: Verbosity
280+
-> Compiler
281+
-> ParStratInstall
282+
-- ^ The parallel strategy
283+
-> Maybe Int
284+
-- ^ A cap on the number of jobs (e.g. to force a maximum of 2 concurrent downloads despite a -j8 parallel strategy)
285+
-> IO (JobControl IO a)
286+
newJobControlFromParStrat verbosity compiler parStrat numJobsCap = case parStrat of
287+
Serial -> newSerialJobControl
288+
NumJobs n -> newParallelJobControl (capJobs (fromMaybe numberOfProcessors n))
289+
UseSem n ->
290+
if jsemSupported compiler
291+
then newSemaphoreJobControl verbosity (capJobs n)
292+
else do
293+
warn verbosity "-jsem is not supported by the selected compiler, falling back to normal parallelism control."
294+
newParallelJobControl (capJobs n)
295+
where
296+
capJobs n = min (fromMaybe maxBound numJobsCap) n
297+
298+
withJobControl :: IO (JobControl IO a) -> (JobControl IO a -> IO b) -> IO b
299+
withJobControl mkJC = bracket mkJC cleanupJobControl
300+
301+
-- | Concurrently execute actions on a list using the given JobControl.
302+
-- The maximum number of concurrent jobs is tied to the JobControl instance.
303+
-- The resulting list does /not/ preserve the original order!
304+
mapConcurrentWithJobs :: JobControl IO b -> (a -> IO b) -> [a] -> IO [b]
305+
mapConcurrentWithJobs jobControl f xs = do
306+
traverse_ (spawnJob jobControl . f) xs
307+
traverse (const $ collectJob jobControl) xs

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

Lines changed: 5 additions & 15 deletions
Original file line numberDiff line numberDiff line change
@@ -88,7 +88,7 @@ import qualified Data.Set as Set
8888

8989
import qualified Text.PrettyPrint as Disp
9090

91-
import Control.Exception (assert, bracket, handle)
91+
import Control.Exception (assert, handle)
9292
import System.Directory (doesDirectoryExist, doesFileExist, renameDirectory)
9393
import System.FilePath (makeRelative, normalise, takeDirectory, (<.>), (</>))
9494
import System.Semaphore (SemaphoreName (..))
@@ -98,7 +98,6 @@ import Distribution.Simple.Flag (fromFlagOrDefault)
9898

9999
import Distribution.Client.ProjectBuilding.PackageFileMonitor
100100
import Distribution.Client.ProjectBuilding.UnpackedPackage (annotateFailureNoLog, buildAndInstallUnpackedPackage, buildInplaceUnpackedPackage)
101-
import Distribution.Client.Utils (numberOfProcessors)
102101

103102
------------------------------------------------------------------------------
104103

@@ -355,17 +354,6 @@ rebuildTargets
355354
}
356355
| fromFlagOrDefault False (projectConfigOfflineMode config) && not (null packagesToDownload) = return offlineError
357356
| otherwise = do
358-
-- Concurrency control: create the job controller and concurrency limits
359-
-- for downloading, building and installing.
360-
mkJobControl <- case buildSettingNumJobs of
361-
Serial -> newSerialJobControl
362-
NumJobs n -> newParallelJobControl (fromMaybe numberOfProcessors n)
363-
UseSem n ->
364-
if jsemSupported compiler
365-
then newSemaphoreJobControl verbosity n
366-
else do
367-
warn verbosity "-jsem is not supported by the selected compiler, falling back to normal parallelism control."
368-
newParallelJobControl n
369357
registerLock <- newLock -- serialise registration
370358
cacheLock <- newLock -- serialise access to setup exe cache
371359
-- TODO: [code cleanup] eliminate setup exe cache
@@ -380,7 +368,9 @@ rebuildTargets
380368
createDirectoryIfMissingVerbose verbosity True distTempDirectory
381369
traverse_ (createPackageDBIfMissing verbosity compiler progdb) packageDBsToUse
382370

383-
bracket (pure mkJobControl) cleanupJobControl $ \jobControl -> do
371+
-- Concurrency control: create the job controller and concurrency limits
372+
-- for downloading, building and installing.
373+
withJobControl (newJobControlFromParStrat verbosity compiler buildSettingNumJobs Nothing) $ \jobControl -> do
384374
-- Before traversing the install plan, preemptively find all packages that
385375
-- will need to be downloaded and start downloading them.
386376
asyncDownloadPackages
@@ -391,7 +381,7 @@ rebuildTargets
391381
$ \downloadMap ->
392382
-- For each package in the plan, in dependency order, but in parallel...
393383
InstallPlan.execute
394-
mkJobControl
384+
jobControl
395385
keepGoing
396386
(BuildFailure Nothing . DependentFailed . packageId)
397387
installPlan

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

Lines changed: 48 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -55,10 +55,14 @@ module Distribution.Client.ProjectConfig
5555
, resolveSolverSettings
5656
, BuildTimeSettings (..)
5757
, resolveBuildTimeSettings
58+
, resolveNumJobsSetting
5859

5960
-- * Checking configuration
6061
, checkBadPerPackageCompilerPaths
6162
, BadPerPackageCompilerPaths (..)
63+
64+
-- * Globals
65+
, maxNumFetchJobs
6266
) where
6367

6468
import Distribution.Client.Compat.Prelude
@@ -68,6 +72,7 @@ import Prelude ()
6872
import Distribution.Client.Glob
6973
( isTrivialRootedGlob
7074
)
75+
import Distribution.Client.JobControl
7176
import Distribution.Client.ProjectConfig.Legacy
7277
import Distribution.Client.ProjectConfig.Types
7378
import Distribution.Client.RebuildMonad
@@ -434,12 +439,7 @@ resolveBuildTimeSettings
434439
-- buildSettingLogVerbosity -- defined below, more complicated
435440
buildSettingBuildReports = fromFlag projectConfigBuildReports
436441
buildSettingSymlinkBinDir = flagToList projectConfigSymlinkBinDir
437-
buildSettingNumJobs =
438-
if fromFlag projectConfigUseSemaphore
439-
then UseSem (determineNumJobs projectConfigNumJobs)
440-
else case (determineNumJobs projectConfigNumJobs) of
441-
1 -> Serial
442-
n -> NumJobs (Just n)
442+
buildSettingNumJobs = resolveNumJobsSetting projectConfigUseSemaphore projectConfigNumJobs
443443
buildSettingKeepGoing = fromFlag projectConfigKeepGoing
444444
buildSettingOfflineMode = fromFlag projectConfigOfflineMode
445445
buildSettingKeepTempFiles = fromFlag projectConfigKeepTempFiles
@@ -535,6 +535,20 @@ resolveBuildTimeSettings
535535
| isParallelBuild buildSettingNumJobs = False
536536
| otherwise = False
537537

538+
-- | Determine the number of jobs (ParStrat) from the project config
539+
resolveNumJobsSetting
540+
:: Flag Bool
541+
-- ^ Whether to use a semaphore (-jsem)
542+
-> Flag (Maybe Int)
543+
-- ^ The number of jobs to run concurrently
544+
-> ParStratX Int
545+
resolveNumJobsSetting projectConfigUseSemaphore projectConfigNumJobs =
546+
if fromFlag projectConfigUseSemaphore
547+
then UseSem (determineNumJobs projectConfigNumJobs)
548+
else case (determineNumJobs projectConfigNumJobs) of
549+
1 -> Serial
550+
n -> NumJobs (Just n)
551+
538552
---------------------------------------------
539553
-- Reading and writing project config files
540554
--
@@ -1213,13 +1227,15 @@ mplusMaybeT ma mb = do
12131227
fetchAndReadSourcePackages
12141228
:: Verbosity
12151229
-> DistDirLayout
1230+
-> Compiler
12161231
-> ProjectConfigShared
12171232
-> ProjectConfigBuildOnly
12181233
-> [ProjectPackageLocation]
12191234
-> Rebuild [PackageSpecifier (SourcePackage UnresolvedPkgLoc)]
12201235
fetchAndReadSourcePackages
12211236
verbosity
12221237
distDirLayout
1238+
compiler
12231239
projectConfigShared
12241240
projectConfigBuildOnly
12251241
pkgLocations = do
@@ -1256,7 +1272,9 @@ fetchAndReadSourcePackages
12561272
syncAndReadSourcePackagesRemoteRepos
12571273
verbosity
12581274
distDirLayout
1275+
compiler
12591276
projectConfigShared
1277+
projectConfigBuildOnly
12601278
(fromFlag (projectConfigOfflineMode projectConfigBuildOnly))
12611279
[repo | ProjectPackageRemoteRepo repo <- pkgLocations]
12621280

@@ -1373,16 +1391,23 @@ fetchAndReadSourcePackageRemoteTarball
13731391
syncAndReadSourcePackagesRemoteRepos
13741392
:: Verbosity
13751393
-> DistDirLayout
1394+
-> Compiler
13761395
-> ProjectConfigShared
1396+
-> ProjectConfigBuildOnly
13771397
-> Bool
13781398
-> [SourceRepoList]
13791399
-> Rebuild [PackageSpecifier (SourcePackage UnresolvedPkgLoc)]
13801400
syncAndReadSourcePackagesRemoteRepos
13811401
verbosity
13821402
DistDirLayout{distDownloadSrcDirectory}
1403+
compiler
13831404
ProjectConfigShared
13841405
{ projectConfigProgPathExtra
13851406
}
1407+
ProjectConfigBuildOnly
1408+
{ projectConfigUseSemaphore
1409+
, projectConfigNumJobs
1410+
}
13861411
offlineMode
13871412
repos = do
13881413
repos' <-
@@ -1408,10 +1433,15 @@ syncAndReadSourcePackagesRemoteRepos
14081433
in configureVCS verbosity progPathExtra vcs
14091434

14101435
concat
1411-
<$> sequenceA
1412-
[ rerunIfChanged verbosity monitor repoGroup' $ do
1413-
vcs' <- getConfiguredVCS repoType
1414-
syncRepoGroupAndReadSourcePackages vcs' pathStem repoGroup'
1436+
<$> rerunConcurrentlyIfChanged
1437+
verbosity
1438+
(newJobControlFromParStrat verbosity compiler parStrat (Just maxNumFetchJobs))
1439+
[ ( monitor
1440+
, repoGroup'
1441+
, do
1442+
vcs' <- getConfiguredVCS repoType
1443+
syncRepoGroupAndReadSourcePackages vcs' pathStem repoGroup'
1444+
)
14151445
| repoGroup@((primaryRepo, repoType) : _) <- Map.elems reposByLocation
14161446
, let repoGroup' = map fst repoGroup
14171447
pathStem =
@@ -1424,6 +1454,7 @@ syncAndReadSourcePackagesRemoteRepos
14241454
monitor = newFileMonitor (pathStem <.> "cache")
14251455
]
14261456
where
1457+
parStrat = resolveNumJobsSetting projectConfigUseSemaphore projectConfigNumJobs
14271458
syncRepoGroupAndReadSourcePackages
14281459
:: VCS ConfiguredProgram
14291460
-> FilePath
@@ -1760,3 +1791,10 @@ onlyTopLevelProvenance :: Set ProjectConfigProvenance -> Set ProjectConfigProven
17601791
onlyTopLevelProvenance = Set.filter $ \case
17611792
Implicit -> False
17621793
Explicit ps -> isTopLevelConfigPath ps
1794+
1795+
-- | The maximum amount of fetch jobs that can run concurrently.
1796+
-- For instance, this is used to limit the amount of concurrent downloads from
1797+
-- hackage, or the amount of concurrent git clones for
1798+
-- source-repository-package stanzas.
1799+
maxNumFetchJobs :: Int
1800+
maxNumFetchJobs = 2

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

Lines changed: 4 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -206,12 +206,10 @@ type ProjectConfigSkeleton = CondTree ConfVar [ProjectConfigPath] ProjectConfig
206206
singletonProjectConfigSkeleton :: ProjectConfig -> ProjectConfigSkeleton
207207
singletonProjectConfigSkeleton x = CondNode x mempty mempty
208208

209-
instantiateProjectConfigSkeletonFetchingCompiler :: Monad m => m (OS, Arch, CompilerInfo) -> FlagAssignment -> ProjectConfigSkeleton -> m ProjectConfig
210-
instantiateProjectConfigSkeletonFetchingCompiler fetch flags skel
211-
| null (toListOf traverseCondTreeV skel) = pure $ fst (ignoreConditions skel)
212-
| otherwise = do
213-
(os, arch, impl) <- fetch
214-
pure $ instantiateProjectConfigSkeletonWithCompiler os arch impl flags skel
209+
instantiateProjectConfigSkeletonFetchingCompiler :: (OS, Arch, CompilerInfo) -> FlagAssignment -> ProjectConfigSkeleton -> ProjectConfig
210+
instantiateProjectConfigSkeletonFetchingCompiler (os, arch, impl) flags skel
211+
| null (toListOf traverseCondTreeV skel) = fst (ignoreConditions skel)
212+
| otherwise = instantiateProjectConfigSkeletonWithCompiler os arch impl flags skel
215213

216214
instantiateProjectConfigSkeletonWithCompiler :: OS -> Arch -> CompilerInfo -> FlagAssignment -> ProjectConfigSkeleton -> ProjectConfig
217215
instantiateProjectConfigSkeletonWithCompiler os arch impl _flags skel = go $ mapTreeConds (fst . simplifyWithSysParams os arch impl) skel

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

Lines changed: 10 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -385,17 +385,16 @@ rebuildProjectConfig
385385
$ do
386386
liftIO $ info verbosity "Project settings changed, reconfiguring..."
387387
projectConfigSkeleton <- phaseReadProjectConfig
388-
let fetchCompiler = do
389-
-- have to create the cache directory before configuring the compiler
390-
liftIO $ createDirectoryIfMissingVerbose verbosity True distProjectCacheDirectory
391-
(compiler, Platform arch os, _) <- configureCompiler verbosity distDirLayout (fst (PD.ignoreConditions projectConfigSkeleton) <> cliConfig)
392-
pure (os, arch, compilerInfo compiler)
393388

394-
projectConfig <- instantiateProjectConfigSkeletonFetchingCompiler fetchCompiler mempty projectConfigSkeleton
389+
-- have to create the cache directory before configuring the compiler
390+
liftIO $ createDirectoryIfMissingVerbose verbosity True distProjectCacheDirectory
391+
(compiler, Platform arch os, _) <- configureCompiler verbosity distDirLayout (fst (PD.ignoreConditions projectConfigSkeleton) <> cliConfig)
392+
393+
let projectConfig = instantiateProjectConfigSkeletonFetchingCompiler (os, arch, compilerInfo compiler) mempty projectConfigSkeleton
395394
when (projectConfigDistDir (projectConfigShared $ projectConfig) /= NoFlag) $
396395
liftIO $
397396
warn verbosity "The builddir option is not supported in project and config files. It will be ignored."
398-
localPackages <- phaseReadLocalPackages (projectConfig <> cliConfig)
397+
localPackages <- phaseReadLocalPackages compiler (projectConfig <> cliConfig)
399398
return (projectConfig, localPackages)
400399

401400
let configfiles =
@@ -427,9 +426,11 @@ rebuildProjectConfig
427426
-- NOTE: These are all packages mentioned in the project configuration.
428427
-- Whether or not they will be considered local to the project will be decided by `shouldBeLocal`.
429428
phaseReadLocalPackages
430-
:: ProjectConfig
429+
:: Compiler
430+
-> ProjectConfig
431431
-> Rebuild [PackageSpecifier UnresolvedSourcePackage]
432432
phaseReadLocalPackages
433+
compiler
433434
projectConfig@ProjectConfig
434435
{ projectConfigShared
435436
, projectConfigBuildOnly
@@ -444,6 +445,7 @@ rebuildProjectConfig
444445
fetchAndReadSourcePackages
445446
verbosity
446447
distDirLayout
448+
compiler
447449
projectConfigShared
448450
projectConfigBuildOnly
449451
pkgLocations

0 commit comments

Comments
 (0)