Skip to content

Commit eb4f43c

Browse files
committed
Synchronize VCS repos concurrently
Cloning/synchronising VCS repos can be unnecessarily slow if done serially. By synchronizing the repos concurrently we make much better use of time. Introduces rerunConcurrentlyIfChanged, a Rebuild monad function that runs, from multiple actions, the actions that need rebuilding concurrently.
1 parent 41a72a4 commit eb4f43c

File tree

9 files changed

+167
-73
lines changed

9 files changed

+167
-73
lines changed

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

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

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 & 16 deletions
Original file line numberDiff line numberDiff line change
@@ -74,7 +74,6 @@ import Distribution.Package
7474
import Distribution.Simple.Compiler
7575
( Compiler
7676
, PackageDB (..)
77-
, jsemSupported
7877
)
7978
import Distribution.Simple.Program
8079
import qualified Distribution.Simple.Register as Cabal
@@ -92,7 +91,7 @@ import qualified Data.Set as Set
9291

9392
import qualified Text.PrettyPrint as Disp
9493

95-
import Control.Exception (assert, bracket, handle)
94+
import Control.Exception (assert, handle)
9695
import System.Directory (doesDirectoryExist, doesFileExist, renameDirectory)
9796
import System.FilePath (makeRelative, normalise, takeDirectory, (<.>), (</>))
9897
import System.Semaphore (SemaphoreName (..))
@@ -102,7 +101,6 @@ import Distribution.Simple.Flag (fromFlagOrDefault)
102101

103102
import Distribution.Client.ProjectBuilding.PackageFileMonitor
104103
import Distribution.Client.ProjectBuilding.UnpackedPackage (annotateFailureNoLog, buildAndInstallUnpackedPackage, buildInplaceUnpackedPackage)
105-
import Distribution.Client.Utils (numberOfProcessors)
106104

107105
------------------------------------------------------------------------------
108106

@@ -359,17 +357,6 @@ rebuildTargets
359357
}
360358
| fromFlagOrDefault False (projectConfigOfflineMode config) && not (null packagesToDownload) = return offlineError
361359
| otherwise = do
362-
-- Concurrency control: create the job controller and concurrency limits
363-
-- for downloading, building and installing.
364-
mkJobControl <- case buildSettingNumJobs of
365-
Serial -> newSerialJobControl
366-
NumJobs n -> newParallelJobControl (fromMaybe numberOfProcessors n)
367-
UseSem n ->
368-
if jsemSupported compiler
369-
then newSemaphoreJobControl verbosity n
370-
else do
371-
warn verbosity "-jsem is not supported by the selected compiler, falling back to normal parallelism control."
372-
newParallelJobControl n
373360
registerLock <- newLock -- serialise registration
374361
cacheLock <- newLock -- serialise access to setup exe cache
375362
-- TODO: [code cleanup] eliminate setup exe cache
@@ -384,7 +371,9 @@ rebuildTargets
384371
createDirectoryIfMissingVerbose verbosity True distTempDirectory
385372
traverse_ (createPackageDBIfMissing verbosity compiler progdb) packageDBsToUse
386373

387-
bracket (pure mkJobControl) cleanupJobControl $ \jobControl -> do
374+
-- Concurrency control: create the job controller and concurrency limits
375+
-- for downloading, building and installing.
376+
withJobControl (newJobControlFromParStrat verbosity compiler buildSettingNumJobs Nothing) $ \jobControl -> do
388377
-- Before traversing the install plan, preemptively find all packages that
389378
-- will need to be downloaded and start downloading them.
390379
asyncDownloadPackages
@@ -395,7 +384,7 @@ rebuildTargets
395384
$ \downloadMap ->
396385
-- For each package in the plan, in dependency order, but in parallel...
397386
InstallPlan.execute
398-
mkJobControl
387+
jobControl
399388
keepGoing
400389
(BuildFailure Nothing . DependentFailed . packageId)
401390
installPlan

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

Lines changed: 34 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -51,6 +51,7 @@ module Distribution.Client.ProjectConfig
5151
, resolveSolverSettings
5252
, BuildTimeSettings (..)
5353
, resolveBuildTimeSettings
54+
, resolveNumJobsSetting
5455

5556
-- * Checking configuration
5657
, checkBadPerPackageCompilerPaths
@@ -64,6 +65,7 @@ import Prelude ()
6465
import Distribution.Client.Glob
6566
( isTrivialRootedGlob
6667
)
68+
import Distribution.Client.JobControl
6769
import Distribution.Client.ProjectConfig.Legacy
6870
import Distribution.Client.ProjectConfig.Types
6971
import Distribution.Client.RebuildMonad
@@ -424,12 +426,7 @@ resolveBuildTimeSettings
424426
-- buildSettingLogVerbosity -- defined below, more complicated
425427
buildSettingBuildReports = fromFlag projectConfigBuildReports
426428
buildSettingSymlinkBinDir = flagToList projectConfigSymlinkBinDir
427-
buildSettingNumJobs =
428-
if fromFlag projectConfigUseSemaphore
429-
then UseSem (determineNumJobs projectConfigNumJobs)
430-
else case (determineNumJobs projectConfigNumJobs) of
431-
1 -> Serial
432-
n -> NumJobs (Just n)
429+
buildSettingNumJobs = resolveNumJobsSetting projectConfigUseSemaphore projectConfigNumJobs
433430
buildSettingKeepGoing = fromFlag projectConfigKeepGoing
434431
buildSettingOfflineMode = fromFlag projectConfigOfflineMode
435432
buildSettingKeepTempFiles = fromFlag projectConfigKeepTempFiles
@@ -525,6 +522,15 @@ resolveBuildTimeSettings
525522
| isParallelBuild buildSettingNumJobs = False
526523
| otherwise = False
527524

525+
-- | Determine the number of jobs (ParStrat) from the project config
526+
resolveNumJobsSetting :: Flag Bool -> Flag (Maybe Int) -> ParStratX Int
527+
resolveNumJobsSetting projectConfigUseSemaphore projectConfigNumJobs =
528+
if fromFlag projectConfigUseSemaphore
529+
then UseSem (determineNumJobs projectConfigNumJobs)
530+
else case (determineNumJobs projectConfigNumJobs) of
531+
1 -> Serial
532+
n -> NumJobs (Just n)
533+
528534
---------------------------------------------
529535
-- Reading and writing project config files
530536
--
@@ -1156,13 +1162,15 @@ mplusMaybeT ma mb = do
11561162
fetchAndReadSourcePackages
11571163
:: Verbosity
11581164
-> DistDirLayout
1165+
-> Compiler
11591166
-> ProjectConfigShared
11601167
-> ProjectConfigBuildOnly
11611168
-> [ProjectPackageLocation]
11621169
-> Rebuild [PackageSpecifier (SourcePackage UnresolvedPkgLoc)]
11631170
fetchAndReadSourcePackages
11641171
verbosity
11651172
distDirLayout
1173+
compiler
11661174
projectConfigShared
11671175
projectConfigBuildOnly
11681176
pkgLocations = do
@@ -1199,7 +1207,9 @@ fetchAndReadSourcePackages
11991207
syncAndReadSourcePackagesRemoteRepos
12001208
verbosity
12011209
distDirLayout
1210+
compiler
12021211
projectConfigShared
1212+
projectConfigBuildOnly
12031213
(fromFlag (projectConfigOfflineMode projectConfigBuildOnly))
12041214
[repo | ProjectPackageRemoteRepo repo <- pkgLocations]
12051215

@@ -1316,16 +1326,23 @@ fetchAndReadSourcePackageRemoteTarball
13161326
syncAndReadSourcePackagesRemoteRepos
13171327
:: Verbosity
13181328
-> DistDirLayout
1329+
-> Compiler
13191330
-> ProjectConfigShared
1331+
-> ProjectConfigBuildOnly
13201332
-> Bool
13211333
-> [SourceRepoList]
13221334
-> Rebuild [PackageSpecifier (SourcePackage UnresolvedPkgLoc)]
13231335
syncAndReadSourcePackagesRemoteRepos
13241336
verbosity
13251337
DistDirLayout{distDownloadSrcDirectory}
1338+
compiler
13261339
ProjectConfigShared
13271340
{ projectConfigProgPathExtra
13281341
}
1342+
ProjectConfigBuildOnly
1343+
{ projectConfigUseSemaphore
1344+
, projectConfigNumJobs
1345+
}
13291346
offlineMode
13301347
repos = do
13311348
repos' <-
@@ -1351,10 +1368,15 @@ syncAndReadSourcePackagesRemoteRepos
13511368
in configureVCS verbosity progPathExtra vcs
13521369

13531370
concat
1354-
<$> sequenceA
1355-
[ rerunIfChanged verbosity monitor repoGroup' $ do
1356-
vcs' <- getConfiguredVCS repoType
1357-
syncRepoGroupAndReadSourcePackages vcs' pathStem repoGroup'
1371+
<$> rerunConcurrentlyIfChanged
1372+
verbosity
1373+
(newJobControlFromParStrat verbosity compiler parStrat maxNumFetchJobs)
1374+
[ ( monitor
1375+
, repoGroup'
1376+
, do
1377+
vcs' <- getConfiguredVCS repoType
1378+
syncRepoGroupAndReadSourcePackages vcs' pathStem repoGroup'
1379+
)
13581380
| repoGroup@((primaryRepo, repoType) : _) <- Map.elems reposByLocation
13591381
, let repoGroup' = map fst repoGroup
13601382
pathStem =
@@ -1367,6 +1389,8 @@ syncAndReadSourcePackagesRemoteRepos
13671389
monitor = newFileMonitor (pathStem <.> "cache")
13681390
]
13691391
where
1392+
maxNumFetchJobs = Just 2 -- try to keep this in sync with Distribution.Client.Install's numFetchJobs.
1393+
parStrat = resolveNumJobsSetting projectConfigUseSemaphore projectConfigNumJobs
13701394
syncRepoGroupAndReadSourcePackages
13711395
:: VCS ConfiguredProgram
13721396
-> FilePath

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

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

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

215213
instantiateProjectConfigSkeletonWithCompiler :: OS -> Arch -> CompilerInfo -> FlagAssignment -> ProjectConfigSkeleton -> ProjectConfig
216214
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
@@ -381,17 +381,16 @@ rebuildProjectConfig
381381
$ do
382382
liftIO $ info verbosity "Project settings changed, reconfiguring..."
383383
projectConfigSkeleton <- phaseReadProjectConfig
384-
let fetchCompiler = do
385-
-- have to create the cache directory before configuring the compiler
386-
liftIO $ createDirectoryIfMissingVerbose verbosity True distProjectCacheDirectory
387-
(compiler, Platform arch os, _) <- configureCompiler verbosity distDirLayout (fst (PD.ignoreConditions projectConfigSkeleton) <> cliConfig)
388-
pure (os, arch, compilerInfo compiler)
389384

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

397396
sequence_
@@ -423,9 +422,11 @@ rebuildProjectConfig
423422
-- NOTE: These are all packages mentioned in the project configuration.
424423
-- Whether or not they will be considered local to the project will be decided by `shouldBeLocal`.
425424
phaseReadLocalPackages
426-
:: ProjectConfig
425+
:: Compiler
426+
-> ProjectConfig
427427
-> Rebuild [PackageSpecifier UnresolvedSourcePackage]
428428
phaseReadLocalPackages
429+
compiler
429430
projectConfig@ProjectConfig
430431
{ projectConfigShared
431432
, projectConfigBuildOnly
@@ -440,6 +441,7 @@ rebuildProjectConfig
440441
fetchAndReadSourcePackages
441442
verbosity
442443
distDirLayout
444+
compiler
443445
projectConfigShared
444446
projectConfigBuildOnly
445447
pkgLocations

0 commit comments

Comments
 (0)