project planning: fix #10686 regression
[cabal.git] / cabal-install / src / Distribution / Client / ProjectPlanning.hs
blobc04bca730d746f9b1049f74486ea5ab2046463f9
1 {-# LANGUAGE DataKinds #-}
2 {-# LANGUAGE DeriveFunctor #-}
3 {-# LANGUAGE LambdaCase #-}
4 {-# LANGUAGE NamedFieldPuns #-}
5 {-# LANGUAGE RankNTypes #-}
6 {-# LANGUAGE RecordWildCards #-}
7 {-# LANGUAGE TypeFamilies #-}
9 -- |
10 -- /Elaborated: worked out with great care and nicety of detail; executed with great minuteness: elaborate preparations; elaborate care./
12 -- In this module we construct an install plan that includes all the information needed to execute it.
14 -- Building a project is therefore split into two phases:
16 -- 1. The construction of the install plan (which as far as possible should be pure), done here.
17 -- 2. The execution of the plan, done in "ProjectBuilding"
19 -- To achieve this we need a representation of this fully elaborated install plan; this representation
20 -- consists of two parts:
22 -- * A 'ElaboratedInstallPlan'. This is a 'GenericInstallPlan' with a
23 -- representation of source packages that includes a lot more detail about
24 -- that package's individual configuration
26 -- * A 'ElaboratedSharedConfig'. Some package configuration is the same for
27 -- every package in a plan. Rather than duplicate that info every entry in
28 -- the 'GenericInstallPlan' we keep that separately.
30 -- The division between the shared and per-package config is not set in stone
31 -- for all time. For example if we wanted to generalise the install plan to
32 -- describe a situation where we want to build some packages with GHC and some
33 -- with GHCJS then the platform and compiler would no longer be shared between
34 -- all packages but would have to be per-package (probably with some sanity
35 -- condition on the graph structure).
36 module Distribution.Client.ProjectPlanning
37 ( -- * Types for the elaborated install plan
38 ElaboratedInstallPlan
39 , ElaboratedConfiguredPackage (..)
40 , ElaboratedPlanPackage
41 , ElaboratedSharedConfig (..)
42 , ElaboratedReadyPackage
43 , BuildStyle (..)
44 , CabalFileText
46 -- * Reading the project configuration
47 -- $readingTheProjectConfiguration
48 , rebuildProjectConfig
50 -- * Producing the elaborated install plan
51 , rebuildInstallPlan
53 -- * Build targets
54 , availableTargets
55 , AvailableTarget (..)
56 , AvailableTargetStatus (..)
57 , TargetRequested (..)
58 , ComponentTarget (..)
59 , SubComponentTarget (..)
60 , showComponentTarget
61 , nubComponentTargets
63 -- * Selecting a plan subset
64 , pruneInstallPlanToTargets
65 , TargetAction (..)
66 , pruneInstallPlanToDependencies
67 , CannotPruneDependencies (..)
69 -- * Utils required for building
70 , pkgHasEphemeralBuildTargets
71 , elabBuildTargetWholeComponents
72 , configureCompiler
74 -- * Setup.hs CLI flags for building
75 , setupHsScriptOptions
76 , setupHsCommonFlags
77 , setupHsConfigureFlags
78 , setupHsConfigureArgs
79 , setupHsBuildFlags
80 , setupHsBuildArgs
81 , setupHsReplFlags
82 , setupHsReplArgs
83 , setupHsTestFlags
84 , setupHsTestArgs
85 , setupHsBenchFlags
86 , setupHsBenchArgs
87 , setupHsCopyFlags
88 , setupHsRegisterFlags
89 , setupHsHaddockFlags
90 , setupHsHaddockArgs
91 , packageHashInputs
93 -- * Path construction
94 , binDirectoryFor
95 , binDirectories
96 , storePackageInstallDirs
97 , storePackageInstallDirs'
98 ) where
100 import Distribution.Client.Compat.Prelude
101 import Text.PrettyPrint
102 ( colon
103 , comma
104 , fsep
105 , hang
106 , punctuate
107 , quotes
108 , render
109 , text
110 , vcat
111 , ($$)
113 import Prelude ()
115 import Distribution.Client.Config
116 import Distribution.Client.Dependency
117 import Distribution.Client.DistDirLayout
118 import Distribution.Client.FetchUtils
119 import Distribution.Client.HashValue
120 import Distribution.Client.HttpUtils
121 import Distribution.Client.JobControl
122 import Distribution.Client.PackageHash
123 import Distribution.Client.ProjectConfig
124 import Distribution.Client.ProjectConfig.Legacy
125 import Distribution.Client.ProjectPlanOutput
126 import Distribution.Client.ProjectPlanning.SetupPolicy
127 ( NonSetupLibDepSolverPlanPackage (..)
128 , mkDefaultSetupDeps
129 , packageSetupScriptSpecVersion
130 , packageSetupScriptStyle
132 import Distribution.Client.ProjectPlanning.Types as Ty
133 import Distribution.Client.RebuildMonad
134 import Distribution.Client.Setup hiding (cabalVersion, packageName)
135 import Distribution.Client.SetupWrapper
136 import Distribution.Client.Store
137 import Distribution.Client.Targets (userToPackageConstraint)
138 import Distribution.Client.Types
139 import Distribution.Client.Utils (concatMapM, incVersion)
141 import qualified Distribution.Client.BuildReports.Storage as BuildReports
142 import qualified Distribution.Client.IndexUtils as IndexUtils
143 import qualified Distribution.Client.InstallPlan as InstallPlan
144 import qualified Distribution.Client.SolverInstallPlan as SolverInstallPlan
146 import Distribution.CabalSpecVersion
147 import Distribution.Utils.LogProgress
148 import Distribution.Utils.MapAccum
149 import Distribution.Utils.NubList
150 import Distribution.Utils.Path hiding
151 ( (<.>)
152 , (</>)
155 import qualified Hackage.Security.Client as Sec
157 import Distribution.Solver.Types.ConstraintSource
158 import Distribution.Solver.Types.InstSolverPackage
159 import Distribution.Solver.Types.LabeledPackageConstraint
160 import Distribution.Solver.Types.OptionalStanza
161 import Distribution.Solver.Types.PkgConfigDb
162 import Distribution.Solver.Types.Settings
163 import Distribution.Solver.Types.SolverId
164 import Distribution.Solver.Types.SolverPackage
165 import Distribution.Solver.Types.SourcePackage
167 import Distribution.ModuleName
168 import Distribution.Package
169 import Distribution.Simple.Compiler
170 import Distribution.Simple.Flag
171 import Distribution.Simple.LocalBuildInfo
172 ( Component (..)
173 , componentBuildInfo
174 , componentName
175 , pkgComponents
178 import Distribution.Simple.BuildWay
179 import Distribution.Simple.PackageIndex (InstalledPackageIndex)
180 import Distribution.Simple.Program
181 import Distribution.Simple.Program.Db
182 import Distribution.Simple.Program.Find
183 import Distribution.System
185 import Distribution.Types.AnnotatedId
186 import Distribution.Types.ComponentInclude
187 import Distribution.Types.ComponentName
188 import Distribution.Types.DependencySatisfaction
189 ( DependencySatisfaction (..)
191 import Distribution.Types.DumpBuildInfo
192 import Distribution.Types.GivenComponent
193 import Distribution.Types.LibraryName
194 import qualified Distribution.Types.LocalBuildConfig as LBC
195 import Distribution.Types.PackageVersionConstraint
196 import Distribution.Types.PkgconfigDependency
197 import Distribution.Types.UnqualComponentName
199 import Distribution.Backpack
200 import Distribution.Backpack.ComponentsGraph
201 import Distribution.Backpack.ConfiguredComponent
202 import Distribution.Backpack.FullUnitId
203 import Distribution.Backpack.LinkedComponent
204 import Distribution.Backpack.ModuleShape
206 import Distribution.Simple.Utils
207 import Distribution.Verbosity
208 import Distribution.Version
210 import qualified Distribution.InstalledPackageInfo as IPI
211 import qualified Distribution.PackageDescription as PD
212 import qualified Distribution.PackageDescription.Configuration as PD
213 import qualified Distribution.Simple.Configure as Cabal
214 import qualified Distribution.Simple.GHC as GHC
215 import qualified Distribution.Simple.GHCJS as GHCJS
216 import qualified Distribution.Simple.InstallDirs as InstallDirs
217 import qualified Distribution.Simple.LocalBuildInfo as Cabal
218 import qualified Distribution.Simple.Setup as Cabal
219 import qualified Distribution.Solver.Types.ComponentDeps as CD
221 import qualified Distribution.Compat.Graph as Graph
223 import Control.Exception (assert)
224 import Control.Monad (sequence)
225 import Control.Monad.IO.Class (liftIO)
226 import Control.Monad.State as State (State, execState, runState, state)
227 import Data.Foldable (fold)
228 import Data.List (deleteBy, groupBy)
229 import qualified Data.List.NonEmpty as NE
230 import qualified Data.Map as Map
231 import qualified Data.Set as Set
232 import Distribution.Client.Errors
233 import Distribution.Solver.Types.ProjectConfigPath
234 import System.FilePath
235 import qualified Text.PrettyPrint as Disp
237 -- | Check that an 'ElaboratedConfiguredPackage' actually makes
238 -- sense under some 'ElaboratedSharedConfig'.
239 sanityCheckElaboratedConfiguredPackage
240 :: ElaboratedSharedConfig
241 -> ElaboratedConfiguredPackage
242 -> a
243 -> a
244 sanityCheckElaboratedConfiguredPackage
245 sharedConfig
246 elab@ElaboratedConfiguredPackage{..} =
247 ( case elabPkgOrComp of
248 ElabPackage pkg -> sanityCheckElaboratedPackage elab pkg
249 ElabComponent comp -> sanityCheckElaboratedComponent elab comp
251 -- The assertion below fails occasionally for unknown reason
252 -- so it was muted until we figure it out, otherwise it severely
253 -- hinders our ability to share and test development builds of cabal-install.
254 -- Tracking issue: https://github.com/haskell/cabal/issues/6006
256 -- either a package is being built inplace, or the
257 -- 'installedPackageId' we assigned is consistent with
258 -- the 'hashedInstalledPackageId' we would compute from
259 -- the elaborated configured package
260 . assert
261 ( isInplaceBuildStyle elabBuildStyle
262 || elabComponentId
263 == hashedInstalledPackageId
264 (packageHashInputs sharedConfig elab)
266 -- the stanzas explicitly disabled should not be available
267 . assert
268 ( optStanzaSetNull $
269 optStanzaKeysFilteredByValue (maybe False not) elabStanzasRequested `optStanzaSetIntersection` elabStanzasAvailable
271 -- either a package is built inplace, or we are not attempting to
272 -- build any test suites or benchmarks (we never build these
273 -- for remote packages!)
274 . assert
275 ( isInplaceBuildStyle elabBuildStyle
276 || optStanzaSetNull elabStanzasAvailable
279 sanityCheckElaboratedComponent
280 :: ElaboratedConfiguredPackage
281 -> ElaboratedComponent
282 -> a
283 -> a
284 sanityCheckElaboratedComponent
285 ElaboratedConfiguredPackage{..}
286 ElaboratedComponent{..} =
287 -- Should not be building bench or test if not inplace.
288 assert
289 ( isInplaceBuildStyle elabBuildStyle
290 || case compComponentName of
291 Nothing -> True
292 Just (CLibName _) -> True
293 Just (CExeName _) -> True
294 -- This is interesting: there's no way to declare a dependency
295 -- on a foreign library at the moment, but you may still want
296 -- to install these to the store
297 Just (CFLibName _) -> True
298 Just (CBenchName _) -> False
299 Just (CTestName _) -> False
302 sanityCheckElaboratedPackage
303 :: ElaboratedConfiguredPackage
304 -> ElaboratedPackage
305 -> a
306 -> a
307 sanityCheckElaboratedPackage
308 ElaboratedConfiguredPackage{..}
309 ElaboratedPackage{..} =
310 -- we should only have enabled stanzas that actually can be built
311 -- (according to the solver)
312 assert (pkgStanzasEnabled `optStanzaSetIsSubset` elabStanzasAvailable)
313 -- the stanzas that the user explicitly requested should be
314 -- enabled (by the previous test, they are also available)
315 . assert
316 ( optStanzaKeysFilteredByValue (fromMaybe False) elabStanzasRequested
317 `optStanzaSetIsSubset` pkgStanzasEnabled
320 -- $readingTheProjectConfiguration
322 -- The project configuration is assembled into a ProjectConfig as follows:
324 -- CLI arguments are converted using "commandLineFlagsToProjectConfig" in the
325 -- v2 command entrypoints and passed to "establishProjectBaseContext" which
326 -- then calls "rebuildProjectConfig".
328 -- "rebuildProjectConfig" then calls "readProjectConfig" to read the project
329 -- files. Due to the presence of conditionals, this output is in the form of a
330 -- "ProjectConfigSkeleton" and will be resolved by "rebuildProjectConfig" using
331 -- "instantiateProjectConfigSkeletonFetchingCompiler".
333 -- "readProjectConfig" also loads the global configuration, which is read with
334 -- "loadConfig" and convertd to a "ProjectConfig" with "convertLegacyGlobalConfig".
336 -- *Important:* You can notice how some project config options are needed to read the
337 -- project config! This is evident by the fact that "rebuildProjectConfig"
338 -- takes "HttpTransport" and "DistDirLayout" as parameters. Two arguments are
339 -- infact determined from the CLI alone (in "establishProjectBaseContext").
340 -- Consequently, project files (including global configuration) cannot
341 -- affect those parameters!
343 -- Furthermore, the project configuration can specify a compiler to use,
344 -- which we need to resolve the conditionals in the project configuration!
345 -- To solve this, we configure the compiler from what is obtained by applying
346 -- the CLI configuration over the the configuration obtained by "flattening"
347 -- ProjectConfigSkeleton. This means collapsing all conditionals by taking
348 -- both branches.
350 -- | Return the up-to-date project config and information about the local
351 -- packages within the project.
352 rebuildProjectConfig
353 :: Verbosity
354 -> HttpTransport
355 -> DistDirLayout
356 -> ProjectConfig
357 -> IO
358 ( ProjectConfig
359 , [PackageSpecifier UnresolvedSourcePackage]
361 rebuildProjectConfig
362 verbosity
363 httpTransport
364 distDirLayout@DistDirLayout
365 { distProjectRootDirectory
366 , distDirectory
367 , distProjectCacheFile
368 , distProjectCacheDirectory
369 , distProjectFile
371 cliConfig = do
372 progsearchpath <- liftIO $ getSystemSearchPath
374 let fileMonitorProjectConfig = newFileMonitor (distProjectCacheFile "config")
376 fileMonitorProjectConfigKey <- do
377 configPath <- getConfigFilePath projectConfigConfigFile
378 return
379 ( configPath
380 , distProjectFile ""
381 , (projectConfigHcFlavor, projectConfigHcPath, projectConfigHcPkg)
382 , progsearchpath
383 , packageConfigProgramPaths
384 , packageConfigProgramPathExtra
387 (projectConfig, localPackages) <-
388 runRebuild distProjectRootDirectory
389 $ rerunIfChanged
390 verbosity
391 fileMonitorProjectConfig
392 fileMonitorProjectConfigKey -- todo check deps too?
393 $ do
394 liftIO $ info verbosity "Project settings changed, reconfiguring..."
395 projectConfigSkeleton <- phaseReadProjectConfig
397 let fetchCompiler = do
398 -- have to create the cache directory before configuring the compiler
399 liftIO $ createDirectoryIfMissingVerbose verbosity True distProjectCacheDirectory
400 (compiler, Platform arch os, _) <- configureCompiler verbosity distDirLayout (fst (PD.ignoreConditions projectConfigSkeleton) <> cliConfig)
401 pure (os, arch, compiler)
403 (projectConfig, compiler) <- instantiateProjectConfigSkeletonFetchingCompiler fetchCompiler mempty projectConfigSkeleton
404 when (projectConfigDistDir (projectConfigShared $ projectConfig) /= NoFlag) $
405 liftIO $
406 warn verbosity "The builddir option is not supported in project and config files. It will be ignored."
407 localPackages <- phaseReadLocalPackages compiler (projectConfig <> cliConfig)
408 return (projectConfig, localPackages)
410 let configfiles =
411 [ text "-" <+> docProjectConfigPath path
412 | Explicit path <- Set.toList . (if verbosity >= verbose then id else onlyTopLevelProvenance) $ projectConfigProvenance projectConfig
414 unless (null configfiles) $
415 notice (verboseStderr verbosity) . render . vcat $
416 text "Configuration is affected by the following files:" : configfiles
418 return (projectConfig <> cliConfig, localPackages)
419 where
420 ProjectConfigShared{projectConfigHcFlavor, projectConfigHcPath, projectConfigHcPkg, projectConfigIgnoreProject, projectConfigConfigFile} =
421 projectConfigShared cliConfig
423 PackageConfig{packageConfigProgramPaths, packageConfigProgramPathExtra} =
424 projectConfigLocalPackages cliConfig
426 -- Read the cabal.project (or implicit config) and combine it with
427 -- arguments from the command line
429 phaseReadProjectConfig :: Rebuild ProjectConfigSkeleton
430 phaseReadProjectConfig = do
431 readProjectConfig verbosity httpTransport projectConfigIgnoreProject projectConfigConfigFile distDirLayout
433 -- Look for all the cabal packages in the project
434 -- some of which may be local src dirs, tarballs etc
436 -- NOTE: These are all packages mentioned in the project configuration.
437 -- Whether or not they will be considered local to the project will be decided by `shouldBeLocal`.
438 phaseReadLocalPackages
439 :: Maybe Compiler
440 -> ProjectConfig
441 -> Rebuild [PackageSpecifier UnresolvedSourcePackage]
442 phaseReadLocalPackages
443 compiler
444 projectConfig@ProjectConfig
445 { projectConfigShared
446 , projectConfigBuildOnly
447 } = do
448 pkgLocations <- findProjectPackages distDirLayout projectConfig
449 -- Create folder only if findProjectPackages did not throw a
450 -- BadPackageLocations exception.
451 liftIO $ do
452 createDirectoryIfMissingVerbose verbosity True distDirectory
453 createDirectoryIfMissingVerbose verbosity True distProjectCacheDirectory
455 fetchAndReadSourcePackages
456 verbosity
457 distDirLayout
458 compiler
459 projectConfigShared
460 projectConfigBuildOnly
461 pkgLocations
463 configureCompiler
464 :: Verbosity
465 -> DistDirLayout
466 -> ProjectConfig
467 -> Rebuild (Compiler, Platform, ProgramDb)
468 configureCompiler
469 verbosity
470 DistDirLayout
471 { distProjectCacheFile
473 ProjectConfig
474 { projectConfigShared =
475 ProjectConfigShared
476 { projectConfigHcFlavor
477 , projectConfigHcPath
478 , projectConfigHcPkg
480 , projectConfigLocalPackages =
481 PackageConfig
482 { packageConfigProgramPaths
483 , packageConfigProgramPathExtra
485 } = do
486 let fileMonitorCompiler = newFileMonitor $ distProjectCacheFile "compiler"
488 progsearchpath <- liftIO $ getSystemSearchPath
490 rerunIfChanged
491 verbosity
492 fileMonitorCompiler
493 ( hcFlavor
494 , hcPath
495 , hcPkg
496 , progsearchpath
497 , packageConfigProgramPaths
498 , packageConfigProgramPathExtra
500 $ do
501 liftIO $ info verbosity "Compiler settings changed, reconfiguring..."
502 let extraPath = fromNubList packageConfigProgramPathExtra
503 progdb <- liftIO $ prependProgramSearchPath verbosity extraPath [] defaultProgramDb
504 let progdb' = userSpecifyPaths (Map.toList (getMapLast packageConfigProgramPaths)) progdb
505 result@(_, _, progdb'') <-
506 liftIO $
507 Cabal.configCompilerEx
508 hcFlavor
509 hcPath
510 hcPkg
511 progdb'
512 verbosity
514 -- Note that we added the user-supplied program locations and args
515 -- for /all/ programs, not just those for the compiler prog and
516 -- compiler-related utils. In principle we don't know which programs
517 -- the compiler will configure (and it does vary between compilers).
518 -- We do know however that the compiler will only configure the
519 -- programs it cares about, and those are the ones we monitor here.
520 monitorFiles (programsMonitorFiles progdb'')
522 -- Note: There is currently a bug here: we are dropping unconfigured
523 -- programs from the 'ProgramDb' when we re-use the cache created by
524 -- 'rerunIfChanged'.
526 -- See Note [Caching the result of configuring the compiler]
528 return result
529 where
530 hcFlavor = flagToMaybe projectConfigHcFlavor
531 hcPath = flagToMaybe projectConfigHcPath
532 hcPkg = flagToMaybe projectConfigHcPkg
534 {- Note [Caching the result of configuring the compiler]
535 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
536 We can't straightforwardly cache anything that contains a 'ProgramDb', because
537 the 'Binary' instance for 'ProgramDb' discards all unconfigured programs.
538 See that instance, as well as 'restoreProgramDb', for a few more details.
540 This means that if we try to cache the result of configuring the compiler (which
541 contains a 'ProgramDb'):
543 - On the first run, we will obtain a 'ProgramDb' which may contain several
544 unconfigured programs. In particular, configuring GHC will add tools such
545 as `ar` and `ld` as unconfigured programs to the 'ProgramDb', with custom
546 logic for finding their location based on the location of the GHC binary.
547 - On subsequent runs, if we use the cache created by 'rerunIfChanged', we will
548 deserialise the 'ProgramDb' from disk, which means it won't include any
549 unconfigured programs, which might mean we are unable to find 'ar' or 'ld'.
551 This is not currently a huge problem because, in the Cabal library, we eagerly
552 re-run the configureCompiler step (thus recovering any lost information), but
553 this is wasted work that we should stop doing in Cabal, given that cabal-install
554 has already figured out all the necessary information about the compiler.
556 To fix this bug, we can't simply eagerly configure all unconfigured programs,
557 as was originally attempted, for a couple of reasons:
559 - it does more work than necessary, by configuring programs that we may not
560 end up needing,
561 - it means that we prioritise system executables for built-in build tools
562 (such as `alex` and `happy`), instead of using the proper version for a
563 package or package component, as specified by a `build-tool-depends` stanza
564 or by package-level `extra-prog-path` arguments.
565 This lead to bug reports #10633 and #10692.
567 See #9840 for more information about the problems surrounding the lossly
568 Binary ProgramDb instance.
571 ------------------------------------------------------------------------------
573 -- * Deciding what to do: making an 'ElaboratedInstallPlan'
575 ------------------------------------------------------------------------------
577 -- | Return an up-to-date elaborated install plan.
579 -- Two variants of the install plan are returned: with and without packages
580 -- from the store. That is, the \"improved\" plan where source packages are
581 -- replaced by pre-existing installed packages from the store (when their ids
582 -- match), and also the original elaborated plan which uses primarily source
583 -- packages.
585 -- The improved plan is what we use for building, but the original elaborated
586 -- plan is useful for reporting and configuration. For example the @freeze@
587 -- command needs the source package info to know about flag choices and
588 -- dependencies of executables and setup scripts.
590 rebuildInstallPlan
591 :: Verbosity
592 -> DistDirLayout
593 -> CabalDirLayout
594 -> ProjectConfig
595 -> [PackageSpecifier UnresolvedSourcePackage]
596 -> Maybe InstalledPackageIndex
597 -> IO
598 ( ElaboratedInstallPlan -- with store packages
599 , ElaboratedInstallPlan -- with source packages
600 , ElaboratedSharedConfig
601 , IndexUtils.TotalIndexState
602 , IndexUtils.ActiveRepos
604 -- ^ @(improvedPlan, elaboratedPlan, _, _, _)@
605 rebuildInstallPlan
606 verbosity
607 distDirLayout@DistDirLayout
608 { distProjectRootDirectory
609 , distProjectCacheFile
611 CabalDirLayout
612 { cabalStoreDirLayout
613 } = \projectConfig localPackages mbInstalledPackages ->
614 runRebuild distProjectRootDirectory $ do
615 progsearchpath <- liftIO $ getSystemSearchPath
616 let projectConfigMonitored = projectConfig{projectConfigBuildOnly = mempty}
618 -- The overall improved plan is cached
619 rerunIfChanged
620 verbosity
621 fileMonitorImprovedPlan
622 -- react to changes in the project config,
623 -- the package .cabal files and the path
624 (projectConfigMonitored, localPackages, progsearchpath)
625 $ do
626 -- And so is the elaborated plan that the improved plan based on
627 (elaboratedPlan, elaboratedShared, totalIndexState, activeRepos) <-
628 rerunIfChanged
629 verbosity
630 fileMonitorElaboratedPlan
631 ( projectConfigMonitored
632 , localPackages
633 , progsearchpath
635 $ do
636 compilerEtc <- phaseConfigureCompiler projectConfig
637 _ <- phaseConfigurePrograms projectConfig compilerEtc
638 (solverPlan, pkgConfigDB, totalIndexState, activeRepos) <-
639 phaseRunSolver
640 projectConfig
641 compilerEtc
642 localPackages
643 (fromMaybe mempty mbInstalledPackages)
644 ( elaboratedPlan
645 , elaboratedShared
646 ) <-
647 phaseElaboratePlan
648 projectConfig
649 compilerEtc
650 pkgConfigDB
651 solverPlan
652 localPackages
654 phaseMaintainPlanOutputs elaboratedPlan elaboratedShared
655 return (elaboratedPlan, elaboratedShared, totalIndexState, activeRepos)
657 -- The improved plan changes each time we install something, whereas
658 -- the underlying elaborated plan only changes when input config
659 -- changes, so it's worth caching them separately.
660 improvedPlan <- phaseImprovePlan elaboratedPlan elaboratedShared
662 return (improvedPlan, elaboratedPlan, elaboratedShared, totalIndexState, activeRepos)
663 where
664 fileMonitorSolverPlan = newFileMonitorInCacheDir "solver-plan"
665 fileMonitorSourceHashes = newFileMonitorInCacheDir "source-hashes"
666 fileMonitorElaboratedPlan = newFileMonitorInCacheDir "elaborated-plan"
667 fileMonitorImprovedPlan = newFileMonitorInCacheDir "improved-plan"
669 newFileMonitorInCacheDir :: Eq a => FilePath -> FileMonitor a b
670 newFileMonitorInCacheDir = newFileMonitor . distProjectCacheFile
672 -- Configure the compiler we're using.
674 -- This is moderately expensive and doesn't change that often so we cache
675 -- it independently.
677 phaseConfigureCompiler
678 :: ProjectConfig
679 -> Rebuild (Compiler, Platform, ProgramDb)
680 phaseConfigureCompiler = configureCompiler verbosity distDirLayout
682 -- Configuring other programs.
684 -- Having configured the compiler, now we configure all the remaining
685 -- programs. This is to check we can find them, and to monitor them for
686 -- changes.
688 -- TODO: [required eventually] we don't actually do this yet.
690 -- We rely on the fact that the previous phase added the program config for
691 -- all local packages, but that all the programs configured so far are the
692 -- compiler program or related util programs.
694 phaseConfigurePrograms
695 :: ProjectConfig
696 -> (Compiler, Platform, ProgramDb)
697 -> Rebuild ()
698 phaseConfigurePrograms projectConfig (_, _, compilerprogdb) = do
699 -- Users are allowed to specify program locations independently for
700 -- each package (e.g. to use a particular version of a pre-processor
701 -- for some packages). However they cannot do this for the compiler
702 -- itself as that's just not going to work. So we check for this.
703 liftIO $
704 checkBadPerPackageCompilerPaths
705 (configuredPrograms compilerprogdb)
706 (getMapMappend (projectConfigSpecificPackage projectConfig))
708 -- TODO: [required eventually] find/configure other programs that the
709 -- user specifies.
711 -- TODO: [required eventually] find/configure all build-tools
712 -- but note that some of them may be built as part of the plan.
714 -- Run the solver to get the initial install plan.
715 -- This is expensive so we cache it independently.
717 phaseRunSolver
718 :: ProjectConfig
719 -> (Compiler, Platform, ProgramDb)
720 -> [PackageSpecifier UnresolvedSourcePackage]
721 -> InstalledPackageIndex
722 -> Rebuild (SolverInstallPlan, Maybe PkgConfigDb, IndexUtils.TotalIndexState, IndexUtils.ActiveRepos)
723 phaseRunSolver
724 projectConfig@ProjectConfig
725 { projectConfigShared
726 , projectConfigBuildOnly
728 (compiler, platform, progdb)
729 localPackages
730 installedPackages =
731 rerunIfChanged
732 verbosity
733 fileMonitorSolverPlan
734 ( solverSettings
735 , localPackages
736 , localPackagesEnabledStanzas
737 , compiler
738 , platform
739 , programDbSignature progdb
741 $ do
742 installedPkgIndex <-
743 getInstalledPackages
744 verbosity
745 compiler
746 progdb
747 platform
748 corePackageDbs
749 (sourcePkgDb, tis, ar) <-
750 getSourcePackages
751 verbosity
752 withRepoCtx
753 (solverSettingIndexState solverSettings)
754 (solverSettingActiveRepos solverSettings)
755 pkgConfigDB <- getPkgConfigDb verbosity progdb
757 -- TODO: [code cleanup] it'd be better if the Compiler contained the
758 -- ConfiguredPrograms that it needs, rather than relying on the progdb
759 -- since we don't need to depend on all the programs here, just the
760 -- ones relevant for the compiler.
762 liftIO $ do
763 notice verbosity "Resolving dependencies..."
764 planOrError <-
765 foldProgress logMsg (pure . Left) (pure . Right) $
766 planPackages
767 verbosity
768 compiler
769 platform
770 solverSettings
771 (installedPackages <> installedPkgIndex)
772 sourcePkgDb
773 pkgConfigDB
774 localPackages
775 localPackagesEnabledStanzas
776 case planOrError of
777 Left msg -> do
778 reportPlanningFailure projectConfig compiler platform localPackages
779 dieWithException verbosity $ PhaseRunSolverErr msg
780 Right plan -> return (plan, pkgConfigDB, tis, ar)
781 where
782 corePackageDbs :: PackageDBStackCWD
783 corePackageDbs =
784 Cabal.interpretPackageDbFlags False (projectConfigPackageDBs projectConfigShared)
786 withRepoCtx :: (RepoContext -> IO a) -> IO a
787 withRepoCtx =
788 projectConfigWithSolverRepoContext
789 verbosity
790 projectConfigShared
791 projectConfigBuildOnly
793 solverSettings = resolveSolverSettings projectConfig
794 logMsg message rest = debugNoWrap verbosity message >> rest
796 localPackagesEnabledStanzas =
797 Map.fromList
798 [ (pkgname, stanzas)
799 | pkg <- localPackages
800 , -- TODO: misnomer: we should separate
801 -- builtin/global/inplace/local packages
802 -- and packages explicitly mentioned in the project
804 let pkgname = pkgSpecifierTarget pkg
805 testsEnabled =
806 lookupLocalPackageConfig
807 packageConfigTests
808 projectConfig
809 pkgname
810 benchmarksEnabled =
811 lookupLocalPackageConfig
812 packageConfigBenchmarks
813 projectConfig
814 pkgname
815 isLocal = isJust (shouldBeLocal pkg)
816 stanzas
817 | isLocal =
818 Map.fromList $
819 [ (TestStanzas, enabled)
820 | enabled <- flagToList testsEnabled
822 ++ [ (BenchStanzas, enabled)
823 | enabled <- flagToList benchmarksEnabled
825 | otherwise = Map.fromList [(TestStanzas, False), (BenchStanzas, False)]
828 -- Elaborate the solver's install plan to get a fully detailed plan. This
829 -- version of the plan has the final nix-style hashed ids.
831 phaseElaboratePlan
832 :: ProjectConfig
833 -> (Compiler, Platform, ProgramDb)
834 -> Maybe PkgConfigDb
835 -> SolverInstallPlan
836 -> [PackageSpecifier (SourcePackage (PackageLocation loc))]
837 -> Rebuild
838 ( ElaboratedInstallPlan
839 , ElaboratedSharedConfig
841 phaseElaboratePlan
842 ProjectConfig
843 { projectConfigShared
844 , projectConfigAllPackages
845 , projectConfigLocalPackages
846 , projectConfigSpecificPackage
847 , projectConfigBuildOnly
849 (compiler, platform, progdb)
850 pkgConfigDB
851 solverPlan
852 localPackages = do
853 liftIO $ debug verbosity "Elaborating the install plan..."
855 sourcePackageHashes <-
856 rerunIfChanged
857 verbosity
858 fileMonitorSourceHashes
859 (packageLocationsSignature solverPlan)
860 $ getPackageSourceHashes verbosity withRepoCtx solverPlan
862 defaultInstallDirs <- liftIO $ userInstallDirTemplates compiler
863 let installDirs = fmap Cabal.fromFlag $ (fmap Flag defaultInstallDirs) <> (projectConfigInstallDirs projectConfigShared)
864 (elaboratedPlan, elaboratedShared) <-
865 liftIO . runLogProgress verbosity $
866 elaborateInstallPlan
867 verbosity
868 platform
869 compiler
870 progdb
871 pkgConfigDB
872 distDirLayout
873 cabalStoreDirLayout
874 solverPlan
875 localPackages
876 sourcePackageHashes
877 installDirs
878 projectConfigShared
879 projectConfigAllPackages
880 projectConfigLocalPackages
881 (getMapMappend projectConfigSpecificPackage)
882 let instantiatedPlan =
883 instantiateInstallPlan
884 cabalStoreDirLayout
885 installDirs
886 elaboratedShared
887 elaboratedPlan
888 liftIO $ debugNoWrap verbosity (showElaboratedInstallPlan instantiatedPlan)
889 return (instantiatedPlan, elaboratedShared)
890 where
891 withRepoCtx :: (RepoContext -> IO a) -> IO a
892 withRepoCtx =
893 projectConfigWithSolverRepoContext
894 verbosity
895 projectConfigShared
896 projectConfigBuildOnly
898 -- Update the files we maintain that reflect our current build environment.
899 -- In particular we maintain a JSON representation of the elaborated
900 -- install plan (but not the improved plan since that reflects the state
901 -- of the build rather than just the input environment).
903 phaseMaintainPlanOutputs
904 :: ElaboratedInstallPlan
905 -> ElaboratedSharedConfig
906 -> Rebuild ()
907 phaseMaintainPlanOutputs elaboratedPlan elaboratedShared = liftIO $ do
908 debug verbosity "Updating plan.json"
909 writePlanExternalRepresentation
910 distDirLayout
911 elaboratedPlan
912 elaboratedShared
914 -- Improve the elaborated install plan. The elaborated plan consists
915 -- mostly of source packages (with full nix-style hashed ids). Where
916 -- corresponding installed packages already exist in the store, replace
917 -- them in the plan.
919 -- Note that we do monitor the store's package db here, so we will redo
920 -- this improvement phase when the db changes -- including as a result of
921 -- executing a plan and installing things.
923 phaseImprovePlan
924 :: ElaboratedInstallPlan
925 -> ElaboratedSharedConfig
926 -> Rebuild ElaboratedInstallPlan
927 phaseImprovePlan elaboratedPlan elaboratedShared = do
928 liftIO $ debug verbosity "Improving the install plan..."
929 storePkgIdSet <- getStoreEntries cabalStoreDirLayout compiler
930 let improvedPlan =
931 improveInstallPlanWithInstalledPackages
932 storePkgIdSet
933 elaboratedPlan
934 liftIO $ debugNoWrap verbosity (showElaboratedInstallPlan improvedPlan)
935 -- TODO: [nice to have] having checked which packages from the store
936 -- we're using, it may be sensible to sanity check those packages
937 -- by loading up the compiler package db and checking everything
938 -- matches up as expected, e.g. no dangling deps, files deleted.
939 return improvedPlan
940 where
941 compiler = pkgConfigCompiler elaboratedShared
943 -- | If a 'PackageSpecifier' refers to a single package, return Just that
944 -- package.
945 reportPlanningFailure :: ProjectConfig -> Compiler -> Platform -> [PackageSpecifier UnresolvedSourcePackage] -> IO ()
946 reportPlanningFailure projectConfig comp platform pkgSpecifiers =
947 when reportFailure $
948 BuildReports.storeLocal
949 (compilerInfo comp)
950 (fromNubList $ projectConfigSummaryFile . projectConfigBuildOnly $ projectConfig)
951 buildReports
952 platform
953 where
954 -- TODO may want to handle the projectConfigLogFile parameter here, or just remove it entirely?
956 reportFailure = Cabal.fromFlag . projectConfigReportPlanningFailure . projectConfigBuildOnly $ projectConfig
957 pkgids = mapMaybe theSpecifiedPackage pkgSpecifiers
958 buildReports =
959 BuildReports.fromPlanningFailure
960 platform
961 (compilerId comp)
962 pkgids
963 -- TODO we may want to get more flag assignments and merge them here?
964 (packageConfigFlagAssignment . projectConfigAllPackages $ projectConfig)
966 theSpecifiedPackage :: Package pkg => PackageSpecifier pkg -> Maybe PackageId
967 theSpecifiedPackage pkgSpec =
968 case pkgSpec of
969 NamedPackage name [PackagePropertyVersion version] ->
970 PackageIdentifier name <$> trivialRange version
971 NamedPackage _ _ -> Nothing
972 SpecificSourcePackage pkg -> Just $ packageId pkg
973 -- \| If a range includes only a single version, return Just that version.
974 trivialRange :: VersionRange -> Maybe Version
975 trivialRange =
976 foldVersionRange
977 Nothing
978 Just -- "== v"
979 (\_ -> Nothing)
980 (\_ -> Nothing)
981 (\_ _ -> Nothing)
982 (\_ _ -> Nothing)
984 programsMonitorFiles :: ProgramDb -> [MonitorFilePath]
985 programsMonitorFiles progdb =
986 [ monitor
987 | prog <- configuredPrograms progdb
988 , monitor <-
989 monitorFileSearchPath
990 (programMonitorFiles prog)
991 (programPath prog)
994 -- | Select the bits of a 'ProgramDb' to monitor for value changes.
995 -- Use 'programsMonitorFiles' for the files to monitor.
996 programDbSignature :: ProgramDb -> [ConfiguredProgram]
997 programDbSignature progdb =
998 [ prog
999 { programMonitorFiles = []
1000 , programOverrideEnv =
1001 filter
1002 ((/= "PATH") . fst)
1003 (programOverrideEnv prog)
1005 | prog <- configuredPrograms progdb
1008 getInstalledPackages
1009 :: Verbosity
1010 -> Compiler
1011 -> ProgramDb
1012 -> Platform
1013 -> PackageDBStackCWD
1014 -> Rebuild InstalledPackageIndex
1015 getInstalledPackages verbosity compiler progdb platform packagedbs = do
1016 monitorFiles . map monitorFileOrDirectory
1017 =<< liftIO
1018 ( IndexUtils.getInstalledPackagesMonitorFiles
1019 verbosity
1020 compiler
1021 Nothing -- use ambient working directory
1022 (coercePackageDBStack packagedbs)
1023 progdb
1024 platform
1026 liftIO $
1027 IndexUtils.getInstalledPackages
1028 verbosity
1029 compiler
1030 packagedbs
1031 progdb
1034 --TODO: [nice to have] use this but for sanity / consistency checking
1035 getPackageDBContents :: Verbosity
1036 -> Compiler -> ProgramDb -> Platform
1037 -> PackageDB
1038 -> Rebuild InstalledPackageIndex
1039 getPackageDBContents verbosity compiler progdb platform packagedb = do
1040 monitorFiles . map monitorFileOrDirectory
1041 =<< liftIO (IndexUtils.getInstalledPackagesMonitorFiles
1042 verbosity compiler
1043 [packagedb] progdb platform)
1044 liftIO $ do
1045 createPackageDBIfMissing verbosity compiler progdb packagedb
1046 Cabal.getPackageDBContents verbosity compiler
1047 packagedb progdb
1050 getSourcePackages
1051 :: Verbosity
1052 -> (forall a. (RepoContext -> IO a) -> IO a)
1053 -> Maybe IndexUtils.TotalIndexState
1054 -> Maybe IndexUtils.ActiveRepos
1055 -> Rebuild (SourcePackageDb, IndexUtils.TotalIndexState, IndexUtils.ActiveRepos)
1056 getSourcePackages verbosity withRepoCtx idxState activeRepos = do
1057 (sourcePkgDbWithTIS, repos) <-
1058 liftIO $
1059 withRepoCtx $ \repoctx -> do
1060 sourcePkgDbWithTIS <- IndexUtils.getSourcePackagesAtIndexState verbosity repoctx idxState activeRepos
1061 return (sourcePkgDbWithTIS, repoContextRepos repoctx)
1063 traverse_ needIfExists
1064 . IndexUtils.getSourcePackagesMonitorFiles
1065 $ repos
1066 return sourcePkgDbWithTIS
1068 getPkgConfigDb :: Verbosity -> ProgramDb -> Rebuild (Maybe PkgConfigDb)
1069 getPkgConfigDb verbosity progdb = do
1070 dirs <- liftIO $ getPkgConfigDbDirs verbosity progdb
1071 -- Just monitor the dirs so we'll notice new .pc files.
1072 -- Alternatively we could monitor all the .pc files too.
1073 traverse_ monitorDirectoryStatus dirs
1074 liftIO $ readPkgConfigDb verbosity progdb
1076 -- | Select the config values to monitor for changes package source hashes.
1077 packageLocationsSignature
1078 :: SolverInstallPlan
1079 -> [(PackageId, PackageLocation (Maybe FilePath))]
1080 packageLocationsSignature solverPlan =
1081 [ (packageId pkg, srcpkgSource pkg)
1082 | SolverInstallPlan.Configured (SolverPackage{solverPkgSource = pkg}) <-
1083 SolverInstallPlan.toList solverPlan
1086 -- | Get the 'HashValue' for all the source packages where we use hashes,
1087 -- and download any packages required to do so.
1089 -- Note that we don't get hashes for local unpacked packages.
1090 getPackageSourceHashes
1091 :: Verbosity
1092 -> (forall a. (RepoContext -> IO a) -> IO a)
1093 -> SolverInstallPlan
1094 -> Rebuild (Map PackageId PackageSourceHash)
1095 getPackageSourceHashes verbosity withRepoCtx solverPlan = do
1096 -- Determine if and where to get the package's source hash from.
1098 let allPkgLocations :: [(PackageId, PackageLocation (Maybe FilePath))]
1099 allPkgLocations =
1100 [ (packageId pkg, srcpkgSource pkg)
1101 | SolverInstallPlan.Configured (SolverPackage{solverPkgSource = pkg}) <-
1102 SolverInstallPlan.toList solverPlan
1105 -- Tarballs that were local in the first place.
1106 -- We'll hash these tarball files directly.
1107 localTarballPkgs :: [(PackageId, FilePath)]
1108 localTarballPkgs =
1109 [ (pkgid, tarball)
1110 | (pkgid, LocalTarballPackage tarball) <- allPkgLocations
1113 -- Tarballs from remote URLs. We must have downloaded these already
1114 -- (since we extracted the .cabal file earlier)
1115 remoteTarballPkgs =
1116 [ (pkgid, tarball)
1117 | (pkgid, RemoteTarballPackage _ (Just tarball)) <- allPkgLocations
1120 -- tarballs from source-repository-package stanzas
1121 sourceRepoTarballPkgs =
1122 [ (pkgid, tarball)
1123 | (pkgid, RemoteSourceRepoPackage _ (Just tarball)) <- allPkgLocations
1126 -- Tarballs from repositories, either where the repository provides
1127 -- hashes as part of the repo metadata, or where we will have to
1128 -- download and hash the tarball.
1129 repoTarballPkgsWithMetadataUnvalidated :: [(Repo, [PackageId])]
1130 repoTarballPkgsWithoutMetadata :: [(Repo, PackageId)]
1131 ( repoTarballPkgsWithMetadataUnvalidated
1132 , repoTarballPkgsWithoutMetadata
1134 partitionEithers
1135 [ case repo of
1136 RepoSecure{} -> Left (repo, [pkgid])
1137 _ -> Right (repo, pkgid)
1138 | (pkgid, RepoTarballPackage repo _ _) <- allPkgLocations
1141 -- Group up the unvalidated packages by repo so we only read the remote
1142 -- index once per repo (see #10110). The packages are ungrouped here and then regrouped
1143 -- below, it would be better in future to refactor this whole code path so that we don't
1144 -- repeatedly group and ungroup.
1145 repoTarballPkgsWithMetadataUnvalidatedMap = Map.fromListWith (++) repoTarballPkgsWithMetadataUnvalidated
1147 (repoTarballPkgsWithMetadata, repoTarballPkgsToDownloadWithMeta) <- fmap partitionEithers $
1148 liftIO $
1149 withRepoCtx $ \repoctx -> flip concatMapM (Map.toList repoTarballPkgsWithMetadataUnvalidatedMap) $
1150 \(repo, pkgids) ->
1151 verifyFetchedTarballs verbosity repoctx repo pkgids
1153 -- For tarballs from repos that do not have hashes available we now have
1154 -- to check if the packages were downloaded already.
1156 ( repoTarballPkgsToDownloadWithNoMeta
1157 , repoTarballPkgsDownloaded
1158 ) <-
1159 fmap partitionEithers $
1160 liftIO $
1161 sequence
1162 [ do
1163 mtarball <- checkRepoTarballFetched repo pkgid
1164 case mtarball of
1165 Nothing -> return (Left (repo, pkgid))
1166 Just tarball -> return (Right (pkgid, tarball))
1167 | (repo, pkgid) <- repoTarballPkgsWithoutMetadata
1170 let repoTarballPkgsToDownload = repoTarballPkgsToDownloadWithMeta ++ repoTarballPkgsToDownloadWithNoMeta
1171 ( hashesFromRepoMetadata
1172 , repoTarballPkgsNewlyDownloaded
1173 ) <-
1174 -- Avoid having to initialise the repository (ie 'withRepoCtx') if we
1175 -- don't have to. (The main cost is configuring the http client.)
1176 if null repoTarballPkgsToDownload && null repoTarballPkgsWithMetadata
1177 then return (Map.empty, [])
1178 else liftIO $ withRepoCtx $ \repoctx -> do
1179 -- For tarballs from repos that do have hashes available as part of the
1180 -- repo metadata we now load up the index for each repo and retrieve
1181 -- the hashes for the packages
1183 hashesFromRepoMetadata <-
1184 Sec.uncheckClientErrors $ -- TODO: [code cleanup] wrap in our own exceptions
1185 fmap (Map.fromList . concat) $
1186 sequence
1187 -- Reading the repo index is expensive so we group the packages by repo
1188 [ repoContextWithSecureRepo repoctx repo $ \secureRepo ->
1189 Sec.withIndex secureRepo $ \repoIndex ->
1190 sequence
1191 [ do
1192 hash <-
1193 Sec.trusted
1194 <$> Sec.indexLookupHash repoIndex pkgid -- strip off Trusted tag
1196 -- Note that hackage-security currently uses SHA256
1197 -- but this API could in principle give us some other
1198 -- choice in future.
1199 return (pkgid, hashFromTUF hash)
1200 | pkgid <- pkgids
1202 | (repo, pkgids) <-
1203 map (\grp@((repo, _) :| _) -> (repo, map snd (NE.toList grp)))
1204 . NE.groupBy ((==) `on` (remoteRepoName . repoRemote . fst))
1205 . sortBy (compare `on` (remoteRepoName . repoRemote . fst))
1206 $ repoTarballPkgsWithMetadata
1209 -- For tarballs from repos that do not have hashes available, download
1210 -- the ones we previously determined we need.
1212 repoTarballPkgsNewlyDownloaded <-
1213 sequence
1214 [ do
1215 tarball <- fetchRepoTarball verbosity repoctx repo pkgid
1216 return (pkgid, tarball)
1217 | (repo, pkgid) <- repoTarballPkgsToDownload
1220 return
1221 ( hashesFromRepoMetadata
1222 , repoTarballPkgsNewlyDownloaded
1225 -- Hash tarball files for packages where we have to do that. This includes
1226 -- tarballs that were local in the first place, plus tarballs from repos,
1227 -- either previously cached or freshly downloaded.
1229 let allTarballFilePkgs :: [(PackageId, FilePath)]
1230 allTarballFilePkgs =
1231 localTarballPkgs
1232 ++ remoteTarballPkgs
1233 ++ sourceRepoTarballPkgs
1234 ++ repoTarballPkgsDownloaded
1235 ++ repoTarballPkgsNewlyDownloaded
1236 hashesFromTarballFiles <-
1237 liftIO $
1238 fmap Map.fromList $
1239 sequence
1240 [ do
1241 srchash <- readFileHashValue tarball
1242 return (pkgid, srchash)
1243 | (pkgid, tarball) <- allTarballFilePkgs
1245 monitorFiles
1246 [ monitorFile tarball
1247 | (_pkgid, tarball) <- allTarballFilePkgs
1250 -- Return the combination
1251 return $!
1252 hashesFromRepoMetadata
1253 <> hashesFromTarballFiles
1255 -- ------------------------------------------------------------
1257 -- * Installation planning
1259 -- ------------------------------------------------------------
1261 planPackages
1262 :: Verbosity
1263 -> Compiler
1264 -> Platform
1265 -> SolverSettings
1266 -> InstalledPackageIndex
1267 -> SourcePackageDb
1268 -> Maybe PkgConfigDb
1269 -> [PackageSpecifier UnresolvedSourcePackage]
1270 -> Map PackageName (Map OptionalStanza Bool)
1271 -> Progress String String SolverInstallPlan
1272 planPackages
1273 verbosity
1274 comp
1275 platform
1276 SolverSettings{..}
1277 installedPkgIndex
1278 sourcePkgDb
1279 pkgConfigDB
1280 localPackages
1281 pkgStanzasEnable =
1282 resolveDependencies
1283 platform
1284 (compilerInfo comp)
1285 pkgConfigDB
1286 resolverParams
1287 where
1288 -- TODO: [nice to have] disable multiple instances restriction in
1289 -- the solver, but then make sure we can cope with that in the
1290 -- output.
1291 resolverParams :: DepResolverParams
1292 resolverParams =
1293 setMaxBackjumps solverSettingMaxBackjumps
1294 . setIndependentGoals solverSettingIndependentGoals
1295 . setReorderGoals solverSettingReorderGoals
1296 . setCountConflicts solverSettingCountConflicts
1297 . setFineGrainedConflicts solverSettingFineGrainedConflicts
1298 . setMinimizeConflictSet solverSettingMinimizeConflictSet
1299 -- TODO: [required eventually] should only be configurable for
1300 -- custom installs
1301 -- . setAvoidReinstalls solverSettingAvoidReinstalls
1303 -- TODO: [required eventually] should only be configurable for
1304 -- custom installs
1305 -- . setShadowPkgs solverSettingShadowPkgs
1307 . setStrongFlags solverSettingStrongFlags
1308 . setAllowBootLibInstalls solverSettingAllowBootLibInstalls
1309 . setOnlyConstrained solverSettingOnlyConstrained
1310 . setSolverVerbosity verbosity
1311 -- TODO: [required eventually] decide if we need to prefer
1312 -- installed for global packages, or prefer latest even for
1313 -- global packages. Perhaps should be configurable but with a
1314 -- different name than "upgrade-dependencies".
1315 . setPreferenceDefault
1316 ( if Cabal.asBool solverSettingPreferOldest
1317 then PreferAllOldest
1318 else PreferLatestForSelected
1320 {-(if solverSettingUpgradeDeps
1321 then PreferAllLatest
1322 else PreferLatestForSelected)-}
1324 . removeLowerBounds solverSettingAllowOlder
1325 . removeUpperBounds solverSettingAllowNewer
1326 . addDefaultSetupDependencies
1327 ( mkDefaultSetupDeps comp platform
1328 . PD.packageDescription
1329 . srcpkgDescription
1331 . addSetupCabalMinVersionConstraint setupMinCabalVersionConstraint
1332 . addSetupCabalMaxVersionConstraint setupMaxCabalVersionConstraint
1333 . addPreferences
1334 -- preferences from the config file or command line
1335 [ PackageVersionPreference name ver
1336 | PackageVersionConstraint name ver <- solverSettingPreferences
1338 . addConstraints
1339 -- version constraints from the config file or command line
1340 [ LabeledPackageConstraint (userToPackageConstraint pc) src
1341 | (pc, src) <- solverSettingConstraints
1343 . addPreferences
1344 -- enable stanza preference unilaterally, regardless if the user asked
1345 -- accordingly or expressed no preference, to help hint the solver
1346 [ PackageStanzasPreference pkgname stanzas
1347 | pkg <- localPackages
1348 , let pkgname = pkgSpecifierTarget pkg
1349 stanzaM = Map.findWithDefault Map.empty pkgname pkgStanzasEnable
1350 stanzas =
1351 [ stanza | stanza <- [minBound .. maxBound], Map.lookup stanza stanzaM /= Just False
1353 , not (null stanzas)
1355 . addConstraints
1356 -- enable stanza constraints where the user asked to enable
1357 [ LabeledPackageConstraint
1358 ( PackageConstraint
1359 (scopeToplevel pkgname)
1360 (PackagePropertyStanzas stanzas)
1362 ConstraintSourceConfigFlagOrTarget
1363 | pkg <- localPackages
1364 , let pkgname = pkgSpecifierTarget pkg
1365 stanzaM = Map.findWithDefault Map.empty pkgname pkgStanzasEnable
1366 stanzas =
1367 [ stanza | stanza <- [minBound .. maxBound], Map.lookup stanza stanzaM == Just True
1369 , not (null stanzas)
1371 . addConstraints
1372 -- TODO: [nice to have] should have checked at some point that the
1373 -- package in question actually has these flags.
1374 [ LabeledPackageConstraint
1375 ( PackageConstraint
1376 (scopeToplevel pkgname)
1377 (PackagePropertyFlags flags)
1379 ConstraintSourceConfigFlagOrTarget
1380 | (pkgname, flags) <- Map.toList solverSettingFlagAssignments
1382 . addConstraints
1383 -- TODO: [nice to have] we have user-supplied flags for unspecified
1384 -- local packages (as well as specific per-package flags). For the
1385 -- former we just apply all these flags to all local targets which
1386 -- is silly. We should check if the flags are appropriate.
1387 [ LabeledPackageConstraint
1388 ( PackageConstraint
1389 (scopeToplevel pkgname)
1390 (PackagePropertyFlags flags)
1392 ConstraintSourceConfigFlagOrTarget
1393 | let flags = solverSettingFlagAssignment
1394 , not (PD.nullFlagAssignment flags)
1395 , pkg <- localPackages
1396 , let pkgname = pkgSpecifierTarget pkg
1398 $ stdResolverParams
1400 stdResolverParams :: DepResolverParams
1401 stdResolverParams =
1402 -- Note: we don't use the standardInstallPolicy here, since that uses
1403 -- its own addDefaultSetupDependencies that is not appropriate for us.
1404 basicInstallPolicy
1405 installedPkgIndex
1406 sourcePkgDb
1407 localPackages
1409 -- While we can talk to older Cabal versions (we need to be able to
1410 -- do so for custom Setup scripts that require older Cabal lib
1411 -- versions), we have problems talking to some older versions that
1412 -- don't support certain features.
1414 -- For example, Cabal-1.16 and older do not know about build targets.
1415 -- Even worse, 1.18 and older only supported the --constraint flag
1416 -- with source package ids, not --dependency with installed package
1417 -- ids. That is bad because we cannot reliably select the right
1418 -- dependencies in the presence of multiple instances (i.e. the
1419 -- store). See issue #3932. So we require Cabal 1.20 as a minimum.
1421 -- Moreover, lib:Cabal generally only supports the interface of
1422 -- current and past compilers; in fact recent lib:Cabal versions
1423 -- will warn when they encounter a too new or unknown GHC compiler
1424 -- version (c.f. #415). To avoid running into unsupported
1425 -- configurations we encode the compatibility matrix as lower
1426 -- bounds on lib:Cabal here (effectively corresponding to the
1427 -- respective major Cabal version bundled with the respective GHC
1428 -- release).
1430 -- GHC 9.2 needs Cabal >= 3.6
1431 -- GHC 9.0 needs Cabal >= 3.4
1432 -- GHC 8.10 needs Cabal >= 3.2
1433 -- GHC 8.8 needs Cabal >= 3.0
1434 -- GHC 8.6 needs Cabal >= 2.4
1435 -- GHC 8.4 needs Cabal >= 2.2
1436 -- GHC 8.2 needs Cabal >= 2.0
1437 -- GHC 8.0 needs Cabal >= 1.24
1438 -- GHC 7.10 needs Cabal >= 1.22
1440 -- (NB: we don't need to consider older GHCs as Cabal >= 1.20 is
1441 -- the absolute lower bound)
1443 -- TODO: long-term, this compatibility matrix should be
1444 -- stored as a field inside 'Distribution.Compiler.Compiler'
1445 setupMinCabalVersionConstraint
1446 | isGHC, compVer >= mkVersion [9, 10] = mkVersion [3, 12]
1447 | isGHC, compVer >= mkVersion [9, 6] = mkVersion [3, 10]
1448 | isGHC, compVer >= mkVersion [9, 4] = mkVersion [3, 8]
1449 | isGHC, compVer >= mkVersion [9, 2] = mkVersion [3, 6]
1450 | isGHC, compVer >= mkVersion [9, 0] = mkVersion [3, 4]
1451 | isGHC, compVer >= mkVersion [8, 10] = mkVersion [3, 2]
1452 | isGHC, compVer >= mkVersion [8, 8] = mkVersion [3, 0]
1453 | isGHC, compVer >= mkVersion [8, 6] = mkVersion [2, 4]
1454 | isGHC, compVer >= mkVersion [8, 4] = mkVersion [2, 2]
1455 | isGHC, compVer >= mkVersion [8, 2] = mkVersion [2, 0]
1456 | isGHC, compVer >= mkVersion [8, 0] = mkVersion [1, 24]
1457 | isGHC, compVer >= mkVersion [7, 10] = mkVersion [1, 22]
1458 | otherwise = mkVersion [1, 20]
1459 where
1460 isGHC = compFlav `elem` [GHC, GHCJS]
1461 compFlav = compilerFlavor comp
1462 compVer = compilerVersion comp
1464 -- As we can't predict the future, we also place a global upper
1465 -- bound on the lib:Cabal version we know how to interact with:
1467 -- The upper bound is computed by incrementing the current major
1468 -- version twice in order to allow for the current version, as
1469 -- well as the next adjacent major version (one of which will not
1470 -- be released, as only "even major" versions of Cabal are
1471 -- released to Hackage or bundled with proper GHC releases).
1473 -- For instance, if the current version of cabal-install is an odd
1474 -- development version, e.g. Cabal-2.1.0.0, then we impose an
1475 -- upper bound `setup.Cabal < 2.3`; if `cabal-install` is on a
1476 -- stable/release even version, e.g. Cabal-2.2.1.0, the upper
1477 -- bound is `setup.Cabal < 2.4`. This gives us enough flexibility
1478 -- when dealing with development snapshots of Cabal and cabal-install.
1480 setupMaxCabalVersionConstraint =
1481 alterVersion (take 2) $ incVersion 1 $ incVersion 1 cabalVersion
1483 ------------------------------------------------------------------------------
1485 -- * Install plan post-processing
1487 ------------------------------------------------------------------------------
1489 -- This phase goes from the InstallPlan we get from the solver and has to
1490 -- make an elaborated install plan.
1492 -- We go in two steps:
1494 -- 1. elaborate all the source packages that the solver has chosen.
1495 -- 2. swap source packages for pre-existing installed packages wherever
1496 -- possible.
1498 -- We do it in this order, elaborating and then replacing, because the easiest
1499 -- way to calculate the installed package ids used for the replacement step is
1500 -- from the elaborated configuration for each package.
1502 ------------------------------------------------------------------------------
1504 -- * Install plan elaboration
1506 ------------------------------------------------------------------------------
1508 -- Note [SolverId to ConfiguredId]
1509 -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
1510 -- Dependency solving is a per package affair, so after we're done, we
1511 -- end up with 'SolverInstallPlan' that records in 'solverPkgLibDeps'
1512 -- and 'solverPkgExeDeps' what packages provide the libraries and executables
1513 -- needed by each component of the package (phew!) For example, if I have
1515 -- library
1516 -- build-depends: lib
1517 -- build-tool-depends: pkg:exe1
1518 -- build-tools: alex
1520 -- After dependency solving, I find out that this library component has
1521 -- library dependencies on lib-0.2, and executable dependencies on pkg-0.1
1522 -- and alex-0.3 (other components of the package may have different
1523 -- dependencies). Note that I've "lost" the knowledge that I depend
1525 -- * specifically* on the exe1 executable from pkg.
1528 -- So, we have a this graph of packages, and we need to transform it into
1529 -- a graph of components which we are actually going to build. In particular:
1531 -- NODE changes from PACKAGE (SolverPackage) to COMPONENTS (ElaboratedConfiguredPackage)
1532 -- EDGE changes from PACKAGE DEP (SolverId) to COMPONENT DEPS (ConfiguredId)
1534 -- In both cases, what was previously a single node/edge may turn into multiple
1535 -- nodes/edges. Multiple components, because there may be multiple components
1536 -- in a package; multiple component deps, because we may depend upon multiple
1537 -- executables from the same package (and maybe, some day, multiple libraries
1538 -- from the same package.)
1540 -- Let's talk about how to do this transformation. Naively, we might consider
1541 -- just processing each package, converting it into (zero or) one or more
1542 -- components. But we also have to update the edges; this leads to
1543 -- two complications:
1545 -- 1. We don't know what the ConfiguredId of a component is until
1546 -- we've configured it, but we cannot configure a component unless
1547 -- we know the ConfiguredId of all its dependencies. Thus, we must
1548 -- process the 'SolverInstallPlan' in topological order.
1550 -- 2. When we process a package, we know the SolverIds of its
1551 -- dependencies, but we have to do some work to turn these into
1552 -- ConfiguredIds. For example, in the case of build-tool-depends, the
1553 -- SolverId isn't enough to uniquely determine the ConfiguredId we should
1554 -- elaborate to: we have to look at the executable name attached to
1555 -- the package name in the package description to figure it out.
1556 -- At the same time, we NEED to use the SolverId, because there might
1557 -- be multiple versions of the same package in the build plan
1558 -- (due to setup dependencies); we can't just look up the package name
1559 -- from the package description.
1561 -- We can adopt the following strategy:
1563 -- * When a package is transformed into components, record
1564 -- a mapping from SolverId to ALL of the components
1565 -- which were elaborated.
1567 -- * When we look up an edge, we use our knowledge of the
1568 -- component name to *filter* the list of components into
1569 -- the ones we actually wanted to refer to.
1571 -- By the way, we can tell that SolverInstallPlan is not the "right" type
1572 -- because a SolverId cannot adequately represent all possible dependency
1573 -- solver states: we may need to record foo-0.1 multiple times in
1574 -- the solver install plan with different dependencies. This imprecision in the
1575 -- type currently doesn't cause any problems because the dependency solver
1576 -- continues to enforce the single instance restriction regardless of compiler
1577 -- version. The right way to solve this is to come up with something very much
1578 -- like a 'ConfiguredId', in that it incorporates the version choices of its
1579 -- dependencies, but less fine grained.
1581 -- | Produce an elaborated install plan using the policy for local builds with
1582 -- a nix-style shared store.
1584 -- In theory should be able to make an elaborated install plan with a policy
1585 -- matching that of the classic @cabal install --user@ or @--global@
1586 elaborateInstallPlan
1587 :: Verbosity
1588 -> Platform
1589 -> Compiler
1590 -> ProgramDb
1591 -> Maybe PkgConfigDb
1592 -> DistDirLayout
1593 -> StoreDirLayout
1594 -> SolverInstallPlan
1595 -> [PackageSpecifier (SourcePackage (PackageLocation loc))]
1596 -> Map PackageId PackageSourceHash
1597 -> InstallDirs.InstallDirTemplates
1598 -> ProjectConfigShared
1599 -> PackageConfig
1600 -> PackageConfig
1601 -> Map PackageName PackageConfig
1602 -> LogProgress (ElaboratedInstallPlan, ElaboratedSharedConfig)
1603 elaborateInstallPlan
1604 verbosity
1605 platform
1606 compiler
1607 compilerprogdb
1608 pkgConfigDB
1609 distDirLayout@DistDirLayout{..}
1610 storeDirLayout@StoreDirLayout{storePackageDBStack}
1611 solverPlan
1612 localPackages
1613 sourcePackageHashes
1614 defaultInstallDirs
1615 sharedPackageConfig
1616 allPackagesConfig
1617 localPackagesConfig
1618 perPackageConfig = do
1619 x <- elaboratedInstallPlan
1620 return (x, elaboratedSharedConfig)
1621 where
1622 elaboratedSharedConfig =
1623 ElaboratedSharedConfig
1624 { pkgConfigPlatform = platform
1625 , pkgConfigCompiler = compiler
1626 , pkgConfigCompilerProgs = compilerprogdb
1627 , pkgConfigReplOptions = mempty
1630 preexistingInstantiatedPkgs :: Map UnitId FullUnitId
1631 preexistingInstantiatedPkgs =
1632 Map.fromList (mapMaybe f (SolverInstallPlan.toList solverPlan))
1633 where
1634 f (SolverInstallPlan.PreExisting inst)
1635 | let ipkg = instSolverPkgIPI inst
1636 , not (IPI.indefinite ipkg) =
1637 Just
1638 ( IPI.installedUnitId ipkg
1639 , ( FullUnitId
1640 (IPI.installedComponentId ipkg)
1641 (Map.fromList (IPI.instantiatedWith ipkg))
1644 f _ = Nothing
1646 elaboratedInstallPlan
1647 :: LogProgress (InstallPlan.GenericInstallPlan IPI.InstalledPackageInfo ElaboratedConfiguredPackage)
1648 elaboratedInstallPlan =
1649 flip InstallPlan.fromSolverInstallPlanWithProgress solverPlan $ \mapDep planpkg ->
1650 case planpkg of
1651 SolverInstallPlan.PreExisting pkg ->
1652 return [InstallPlan.PreExisting (instSolverPkgIPI pkg)]
1653 SolverInstallPlan.Configured pkg ->
1654 let inplace_doc
1655 | shouldBuildInplaceOnly pkg = text "inplace"
1656 | otherwise = Disp.empty
1657 in addProgressCtx
1658 ( text "In the"
1659 <+> inplace_doc
1660 <+> text "package"
1661 <+> quotes (pretty (packageId pkg))
1663 $ map InstallPlan.Configured <$> elaborateSolverToComponents mapDep pkg
1665 -- NB: We don't INSTANTIATE packages at this point. That's
1666 -- a post-pass. This makes it simpler to compute dependencies.
1667 elaborateSolverToComponents
1668 :: (SolverId -> [ElaboratedPlanPackage])
1669 -> SolverPackage UnresolvedPkgLoc
1670 -> LogProgress [ElaboratedConfiguredPackage]
1671 elaborateSolverToComponents mapDep spkg@(SolverPackage _ _ _ deps0 exe_deps0) =
1672 case mkComponentsGraph (elabEnabledSpec elab0) pd of
1673 Right g -> do
1674 let src_comps = componentsGraphToList g
1675 infoProgress $
1676 hang
1677 (text "Component graph for" <+> pretty pkgid <<>> colon)
1679 (dispComponentsWithDeps src_comps)
1680 (_, comps) <-
1681 mapAccumM
1682 buildComponent
1683 (Map.empty, Map.empty, Map.empty)
1684 (map fst src_comps)
1685 let whyNotPerComp = why_not_per_component src_comps
1686 case NE.nonEmpty whyNotPerComp of
1687 Nothing -> do
1688 elaborationWarnings
1689 return comps
1690 Just notPerCompReasons -> do
1691 checkPerPackageOk comps notPerCompReasons
1692 pkgComp <-
1693 elaborateSolverToPackage
1694 notPerCompReasons
1695 spkg
1697 (comps ++ maybeToList setupComponent)
1698 return [pkgComp]
1699 Left cns ->
1700 dieProgress $
1701 hang
1702 (text "Dependency cycle between the following components:")
1704 (vcat (map (text . componentNameStanza) cns))
1705 where
1706 bt = PD.buildType (elabPkgDescription elab0)
1707 -- You are eligible to per-component build if this list is empty
1708 why_not_per_component g =
1709 cuz_buildtype ++ cuz_spec ++ cuz_length ++ cuz_flag
1710 where
1711 -- We have to disable per-component for now with
1712 -- Configure-type scripts in order to prevent parallel
1713 -- invocation of the same `./configure` script.
1714 -- See https://github.com/haskell/cabal/issues/4548
1716 -- Moreover, at this point in time, only non-Custom setup scripts
1717 -- are supported. Implementing per-component builds with
1718 -- Custom would require us to create a new 'ElabSetup'
1719 -- type, and teach all of the code paths how to handle it.
1720 -- Once you've implemented this, swap it for the code below.
1721 cuz_buildtype =
1722 case bt of
1723 PD.Configure -> [CuzBuildType CuzConfigureBuildType]
1724 PD.Custom -> [CuzBuildType CuzCustomBuildType]
1725 PD.Hooks -> [CuzBuildType CuzHooksBuildType]
1726 PD.Make -> [CuzBuildType CuzMakeBuildType]
1727 PD.Simple -> []
1728 -- cabal-format versions prior to 1.8 have different build-depends semantics
1729 -- for now it's easier to just fallback to legacy-mode when specVersion < 1.8
1730 -- see, https://github.com/haskell/cabal/issues/4121
1731 cuz_spec
1732 | PD.specVersion pd >= CabalSpecV1_8 = []
1733 | otherwise = [CuzCabalSpecVersion]
1734 -- In the odd corner case that a package has no components at all
1735 -- then keep it as a whole package, since otherwise it turns into
1736 -- 0 component graph nodes and effectively vanishes. We want to
1737 -- keep it around at least for error reporting purposes.
1738 cuz_length
1739 | length g > 0 = []
1740 | otherwise = [CuzNoBuildableComponents]
1741 -- For ease of testing, we let per-component builds be toggled
1742 -- at the top level
1743 cuz_flag
1744 | fromFlagOrDefault True (projectConfigPerComponent sharedPackageConfig) =
1746 | otherwise = [CuzDisablePerComponent]
1748 -- \| Sometimes a package may make use of features which are only
1749 -- supported in per-package mode. If this is the case, we should
1750 -- give an error when this occurs.
1751 checkPerPackageOk comps reasons = do
1752 let is_sublib (CLibName (LSubLibName _)) = True
1753 is_sublib _ = False
1754 when (any (matchElabPkg is_sublib) comps) $
1755 dieProgress $
1756 text "Internal libraries only supported with per-component builds."
1757 $$ text "Per-component builds were disabled because"
1758 <+> fsep (punctuate comma $ map (text . whyNotPerComponent) $ toList reasons)
1759 -- TODO: Maybe exclude Backpack too
1761 (elab0, elaborationWarnings) = elaborateSolverToCommon spkg
1762 pkgid = elabPkgSourceId elab0
1763 pd = elabPkgDescription elab0
1765 -- TODO: This is just a skeleton to get elaborateSolverToPackage
1766 -- working correctly
1767 -- TODO: When we actually support building these components, we
1768 -- have to add dependencies on this from all other components
1769 setupComponent :: Maybe ElaboratedConfiguredPackage
1770 setupComponent
1771 | bt `elem` [PD.Custom, PD.Hooks] =
1772 Just
1773 elab0
1774 { elabModuleShape = emptyModuleShape
1775 , elabUnitId = notImpl "elabUnitId"
1776 , elabComponentId = notImpl "elabComponentId"
1777 , elabLinkedInstantiatedWith = Map.empty
1778 , elabInstallDirs = notImpl "elabInstallDirs"
1779 , elabPkgOrComp = ElabComponent (ElaboratedComponent{..})
1781 | otherwise =
1782 Nothing
1783 where
1784 compSolverName = CD.ComponentSetup
1785 compComponentName = Nothing
1787 dep_pkgs = elaborateLibSolverId mapDep =<< CD.setupDeps deps0
1789 compLibDependencies =
1790 -- MP: No idea what this function does
1791 map (\cid -> (configuredId cid, False)) dep_pkgs
1792 compLinkedLibDependencies = notImpl "compLinkedLibDependencies"
1793 compOrderLibDependencies = notImpl "compOrderLibDependencies"
1795 -- Not supported:
1796 compExeDependencies :: [a]
1797 compExeDependencies = []
1799 compExeDependencyPaths :: [a]
1800 compExeDependencyPaths = []
1802 compPkgConfigDependencies :: [a]
1803 compPkgConfigDependencies = []
1805 notImpl f =
1806 error $
1807 "Distribution.Client.ProjectPlanning.setupComponent: "
1808 ++ f
1809 ++ " not implemented yet"
1811 buildComponent
1812 :: ( ConfiguredComponentMap
1813 , LinkedComponentMap
1814 , Map ComponentId FilePath
1816 -> Cabal.Component
1817 -> LogProgress
1818 ( ( ConfiguredComponentMap
1819 , LinkedComponentMap
1820 , Map ComponentId FilePath
1822 , ElaboratedConfiguredPackage
1824 buildComponent (cc_map, lc_map, exe_map) comp =
1825 addProgressCtx
1826 ( text "In the stanza"
1827 <+> quotes (text (componentNameStanza cname))
1829 $ do
1830 -- 1. Configure the component, but with a place holder ComponentId.
1831 cc0 <-
1832 toConfiguredComponent
1834 (error "Distribution.Client.ProjectPlanning.cc_cid: filled in later")
1835 (Map.unionWith Map.union external_lib_cc_map cc_map)
1836 (Map.unionWith Map.union external_exe_cc_map cc_map)
1837 comp
1839 let do_ cid =
1840 let cid' = annotatedIdToConfiguredId . ci_ann_id $ cid
1841 in (cid', False) -- filled in later in pruneInstallPlanPhase2)
1842 -- 2. Read out the dependencies from the ConfiguredComponent cc0
1843 let compLibDependencies =
1844 -- Nub because includes can show up multiple times
1845 ordNub
1846 ( map
1847 (\cid -> do_ cid)
1848 (cc_includes cc0)
1850 compExeDependencies =
1852 annotatedIdToConfiguredId
1853 (cc_exe_deps cc0)
1854 compExeDependencyPaths =
1855 [ (annotatedIdToConfiguredId aid', path)
1856 | aid' <- cc_exe_deps cc0
1857 , Just paths <- [Map.lookup (ann_id aid') exe_map1]
1858 , path <- paths
1860 elab_comp = ElaboratedComponent{..}
1862 -- 3. Construct a preliminary ElaboratedConfiguredPackage,
1863 -- and use this to compute the component ID. Fix up cc_id
1864 -- correctly.
1865 let elab1 =
1866 elab0
1867 { elabPkgOrComp = ElabComponent $ elab_comp
1869 cid = case elabBuildStyle elab0 of
1870 BuildInplaceOnly{} ->
1871 mkComponentId $
1872 prettyShow pkgid
1873 ++ "-inplace"
1874 ++ ( case Cabal.componentNameString cname of
1875 Nothing -> ""
1876 Just s -> "-" ++ prettyShow s
1878 BuildAndInstall ->
1879 hashedInstalledPackageId
1880 ( packageHashInputs
1881 elaboratedSharedConfig
1882 elab1 -- knot tied
1884 cc = cc0{cc_ann_id = fmap (const cid) (cc_ann_id cc0)}
1885 infoProgress $ dispConfiguredComponent cc
1887 -- 4. Perform mix-in linking
1888 let lookup_uid def_uid =
1889 case Map.lookup (unDefUnitId def_uid) preexistingInstantiatedPkgs of
1890 Just full -> full
1891 Nothing -> error ("lookup_uid: " ++ prettyShow def_uid)
1892 lc <-
1893 toLinkedComponent
1894 verbosity
1895 False
1896 lookup_uid
1897 (elabPkgSourceId elab0)
1898 (Map.union external_lc_map lc_map)
1900 infoProgress $ dispLinkedComponent lc
1901 -- NB: elab is setup to be the correct form for an
1902 -- indefinite library, or a definite library with no holes.
1903 -- We will modify it in 'instantiateInstallPlan' to handle
1904 -- instantiated packages.
1906 -- 5. Construct the final ElaboratedConfiguredPackage
1908 elab2 =
1909 elab1
1910 { elabModuleShape = lc_shape lc
1911 , elabUnitId = abstractUnitId (lc_uid lc)
1912 , elabComponentId = lc_cid lc
1913 , elabLinkedInstantiatedWith = Map.fromList (lc_insts lc)
1914 , elabPkgOrComp =
1915 ElabComponent $
1916 elab_comp
1917 { compLinkedLibDependencies = ordNub (map ci_id (lc_includes lc))
1918 , compOrderLibDependencies =
1919 ordNub
1920 ( map
1921 (abstractUnitId . ci_id)
1922 (lc_includes lc ++ lc_sig_includes lc)
1926 elab =
1927 elab2
1928 { elabInstallDirs =
1929 computeInstallDirs
1930 storeDirLayout
1931 defaultInstallDirs
1932 elaboratedSharedConfig
1933 elab2
1936 -- 6. Construct the updated local maps
1937 let cc_map' = extendConfiguredComponentMap cc cc_map
1938 lc_map' = extendLinkedComponentMap lc lc_map
1939 exe_map' = Map.insert cid (inplace_bin_dir elab) exe_map
1941 return ((cc_map', lc_map', exe_map'), elab)
1942 where
1943 compLinkedLibDependencies = error "buildComponent: compLinkedLibDependencies"
1944 compOrderLibDependencies = error "buildComponent: compOrderLibDependencies"
1946 cname = Cabal.componentName comp
1947 compComponentName = Just cname
1948 compSolverName = CD.componentNameToComponent cname
1950 -- NB: compLinkedLibDependencies and
1951 -- compOrderLibDependencies are defined when we define
1952 -- 'elab'.
1953 external_lib_dep_sids = CD.select (== compSolverName) deps0
1954 external_exe_dep_sids = CD.select (== compSolverName) exe_deps0
1956 external_lib_dep_pkgs = concatMap mapDep external_lib_dep_sids
1958 -- Combine library and build-tool dependencies, for backwards
1959 -- compatibility (See issue #5412 and the documentation for
1960 -- InstallPlan.fromSolverInstallPlan), but prefer the versions
1961 -- specified as build-tools.
1962 external_exe_dep_pkgs =
1963 concatMap mapDep $
1964 ordNubBy (pkgName . packageId) $
1965 external_exe_dep_sids ++ external_lib_dep_sids
1967 external_exe_map =
1968 Map.fromList $
1969 [ (getComponentId pkg, paths)
1970 | pkg <- external_exe_dep_pkgs
1971 , let paths = planPackageExePaths pkg
1973 exe_map1 = Map.union external_exe_map $ fmap (\x -> [x]) exe_map
1975 external_lib_cc_map =
1976 Map.fromListWith Map.union $
1977 map mkCCMapping external_lib_dep_pkgs
1978 external_exe_cc_map =
1979 Map.fromListWith Map.union $
1980 map mkCCMapping external_exe_dep_pkgs
1981 external_lc_map =
1982 Map.fromList $
1983 map mkShapeMapping $
1984 external_lib_dep_pkgs ++ concatMap mapDep external_exe_dep_sids
1986 compPkgConfigDependencies =
1987 [ ( pn
1988 , fromMaybe
1989 ( error $
1990 "compPkgConfigDependencies: impossible! "
1991 ++ prettyShow pn
1992 ++ " from "
1993 ++ prettyShow (elabPkgSourceId elab0)
1995 (pkgConfigDB >>= \db -> pkgConfigDbPkgVersion db pn)
1997 | PkgconfigDependency pn _ <-
1998 PD.pkgconfigDepends
1999 (Cabal.componentBuildInfo comp)
2002 inplace_bin_dir elab =
2003 binDirectoryFor
2004 distDirLayout
2005 elaboratedSharedConfig
2006 elab
2007 $ case Cabal.componentNameString cname of
2008 Just n -> prettyShow n
2009 Nothing -> ""
2011 -- \| Given a 'SolverId' referencing a dependency on a library, return
2012 -- the 'ElaboratedPlanPackage' corresponding to the library. This
2013 -- returns at most one result.
2014 elaborateLibSolverId
2015 :: (SolverId -> [ElaboratedPlanPackage])
2016 -> SolverId
2017 -> [ElaboratedPlanPackage]
2018 elaborateLibSolverId mapDep = filter (matchPlanPkg (== (CLibName LMainLibName))) . mapDep
2020 -- \| Given an 'ElaboratedPlanPackage', return the paths to where the
2021 -- executables that this package represents would be installed.
2022 -- The only case where multiple paths can be returned is the inplace
2023 -- monolithic package one, since there can be multiple exes and each one
2024 -- has its own directory.
2025 planPackageExePaths :: ElaboratedPlanPackage -> [FilePath]
2026 planPackageExePaths =
2027 -- Pre-existing executables are assumed to be in PATH
2028 -- already. In fact, this should be impossible.
2029 InstallPlan.foldPlanPackage (const []) $ \elab ->
2031 executables :: [FilePath]
2032 executables =
2033 case elabPkgOrComp elab of
2034 -- Monolithic mode: all exes of the package
2035 ElabPackage _ ->
2036 unUnqualComponentName . PD.exeName
2037 <$> PD.executables (elabPkgDescription elab)
2038 -- Per-component mode: just the selected exe
2039 ElabComponent comp ->
2040 case fmap
2041 Cabal.componentNameString
2042 (compComponentName comp) of
2043 Just (Just n) -> [prettyShow n]
2044 _ -> [""]
2046 binDirectoryFor
2047 distDirLayout
2048 elaboratedSharedConfig
2049 elab
2050 <$> executables
2052 elaborateSolverToPackage
2053 :: NE.NonEmpty NotPerComponentReason
2054 -> SolverPackage UnresolvedPkgLoc
2055 -> ComponentsGraph
2056 -> [ElaboratedConfiguredPackage]
2057 -> LogProgress ElaboratedConfiguredPackage
2058 elaborateSolverToPackage
2059 pkgWhyNotPerComponent
2060 pkg@( SolverPackage
2061 (SourcePackage pkgid _gpd _srcloc _descOverride)
2062 _flags
2063 _stanzas
2064 _deps0
2065 _exe_deps0
2067 compGraph
2068 comps = do
2069 -- Knot tying: the final elab includes the
2070 -- pkgInstalledId, which is calculated by hashing many
2071 -- of the other fields of the elaboratedPackage.
2072 elaborationWarnings
2073 return elab
2074 where
2075 (elab0@ElaboratedConfiguredPackage{..}, elaborationWarnings) =
2076 elaborateSolverToCommon pkg
2078 elab1 =
2079 elab0
2080 { elabUnitId = newSimpleUnitId pkgInstalledId
2081 , elabComponentId = pkgInstalledId
2082 , elabLinkedInstantiatedWith = Map.empty
2083 , elabPkgOrComp = ElabPackage $ ElaboratedPackage{..}
2084 , elabModuleShape = modShape
2087 elab =
2088 elab1
2089 { elabInstallDirs =
2090 computeInstallDirs
2091 storeDirLayout
2092 defaultInstallDirs
2093 elaboratedSharedConfig
2094 elab1
2097 modShape = case find (matchElabPkg (== (CLibName LMainLibName))) comps of
2098 Nothing -> emptyModuleShape
2099 Just e -> Ty.elabModuleShape e
2101 pkgInstalledId
2102 | shouldBuildInplaceOnly pkg =
2103 mkComponentId (prettyShow pkgid ++ "-inplace")
2104 | otherwise =
2105 assert (isJust elabPkgSourceHash) $
2106 hashedInstalledPackageId
2107 ( packageHashInputs
2108 elaboratedSharedConfig
2109 elab -- recursive use of elab
2112 -- Need to filter out internal dependencies, because they don't
2113 -- correspond to anything real anymore.
2114 isExt confid = confSrcId confid /= pkgid
2115 filterExt = filter isExt
2117 filterExt' :: [(ConfiguredId, a)] -> [(ConfiguredId, a)]
2118 filterExt' = filter (isExt . fst)
2120 pkgLibDependencies =
2121 buildComponentDeps (filterExt' . compLibDependencies)
2122 pkgExeDependencies =
2123 buildComponentDeps (filterExt . compExeDependencies)
2124 pkgExeDependencyPaths =
2125 buildComponentDeps (filterExt' . compExeDependencyPaths)
2127 -- TODO: Why is this flat?
2128 pkgPkgConfigDependencies =
2129 CD.flatDeps $ buildComponentDeps compPkgConfigDependencies
2131 pkgDependsOnSelfLib =
2132 CD.fromList
2133 [ (CD.componentNameToComponent cn, [()])
2134 | Graph.N _ cn _ <- fromMaybe [] mb_closure
2136 where
2137 mb_closure = Graph.revClosure compGraph [k | k <- Graph.keys compGraph, is_lib k]
2138 -- NB: the sublib case should not occur, because sub-libraries
2139 -- are not supported without per-component builds
2140 is_lib (CLibName _) = True
2141 is_lib _ = False
2143 buildComponentDeps :: Monoid a => (ElaboratedComponent -> a) -> CD.ComponentDeps a
2144 buildComponentDeps f =
2145 CD.fromList
2146 [ (compSolverName comp, f comp)
2147 | ElaboratedConfiguredPackage{elabPkgOrComp = ElabComponent comp} <- comps
2150 -- NB: This is not the final setting of 'pkgStanzasEnabled'.
2151 -- See [Sticky enabled testsuites]; we may enable some extra
2152 -- stanzas opportunistically when it is cheap to do so.
2154 -- However, we start off by enabling everything that was
2155 -- requested, so that we can maintain an invariant that
2156 -- pkgStanzasEnabled is a superset of elabStanzasRequested
2157 pkgStanzasEnabled = optStanzaKeysFilteredByValue (fromMaybe False) elabStanzasRequested
2159 elaborateSolverToCommon
2160 :: SolverPackage UnresolvedPkgLoc
2161 -> (ElaboratedConfiguredPackage, LogProgress ())
2162 elaborateSolverToCommon
2163 pkg@( SolverPackage
2164 (SourcePackage pkgid gdesc srcloc descOverride)
2165 flags
2166 stanzas
2167 deps0
2168 _exe_deps0
2170 (elaboratedPackage, wayWarnings pkgid)
2171 where
2172 elaboratedPackage = ElaboratedConfiguredPackage{..}
2174 -- These get filled in later
2175 elabUnitId = error "elaborateSolverToCommon: elabUnitId"
2176 elabComponentId = error "elaborateSolverToCommon: elabComponentId"
2177 elabInstantiatedWith = Map.empty
2178 elabLinkedInstantiatedWith = error "elaborateSolverToCommon: elabLinkedInstantiatedWith"
2179 elabPkgOrComp = error "elaborateSolverToCommon: elabPkgOrComp"
2180 elabInstallDirs = error "elaborateSolverToCommon: elabInstallDirs"
2181 elabModuleShape = error "elaborateSolverToCommon: elabModuleShape"
2183 elabIsCanonical = True
2184 elabPkgSourceId = pkgid
2185 elabPkgDescription = case PD.finalizePD
2186 flags
2187 elabEnabledSpec
2188 (const Satisfied)
2189 platform
2190 (compilerInfo compiler)
2192 gdesc of
2193 Right (desc, _) -> desc
2194 Left _ -> error "Failed to finalizePD in elaborateSolverToCommon"
2195 elabFlagAssignment = flags
2196 elabFlagDefaults =
2197 PD.mkFlagAssignment
2198 [ (PD.flagName flag, PD.flagDefault flag)
2199 | flag <- PD.genPackageFlags gdesc
2202 elabEnabledSpec = enableStanzas stanzas
2203 elabStanzasAvailable = stanzas
2205 elabStanzasRequested :: OptionalStanzaMap (Maybe Bool)
2206 elabStanzasRequested = optStanzaTabulate $ \o -> case o of
2207 -- NB: even if a package stanza is requested, if the package
2208 -- doesn't actually have any of that stanza we omit it from
2209 -- the request, to ensure that we don't decide that this
2210 -- package needs to be rebuilt. (It needs to be done here,
2211 -- because the ElaboratedConfiguredPackage is where we test
2212 -- whether or not there have been changes.)
2213 TestStanzas -> listToMaybe [v | v <- maybeToList tests, _ <- PD.testSuites elabPkgDescription]
2214 BenchStanzas -> listToMaybe [v | v <- maybeToList benchmarks, _ <- PD.benchmarks elabPkgDescription]
2215 where
2216 tests, benchmarks :: Maybe Bool
2217 tests = perPkgOptionMaybe pkgid packageConfigTests
2218 benchmarks = perPkgOptionMaybe pkgid packageConfigBenchmarks
2220 -- This is a placeholder which will get updated by 'pruneInstallPlanPass1'
2221 -- and 'pruneInstallPlanPass2'. We can't populate it here
2222 -- because whether or not tests/benchmarks should be enabled
2223 -- is heuristically calculated based on whether or not the
2224 -- dependencies of the test suite have already been installed,
2225 -- but this function doesn't know what is installed (since
2226 -- we haven't improved the plan yet), so we do it in another pass.
2227 -- Check the comments of those functions for more details.
2228 elabConfigureTargets = []
2229 elabBuildTargets = []
2230 elabTestTargets = []
2231 elabBenchTargets = []
2232 elabReplTarget = []
2233 elabHaddockTargets = []
2235 elabBuildHaddocks =
2236 perPkgOptionFlag pkgid False packageConfigDocumentation
2238 -- `documentation: true` should imply `-haddock` for GHC
2239 addHaddockIfDocumentationEnabled :: ConfiguredProgram -> ConfiguredProgram
2240 addHaddockIfDocumentationEnabled cp@ConfiguredProgram{..} =
2241 if programId == "ghc" && elabBuildHaddocks
2242 then cp{programOverrideArgs = "-haddock" : programOverrideArgs}
2243 else cp
2245 elabPkgSourceLocation = srcloc
2246 elabPkgSourceHash = Map.lookup pkgid sourcePackageHashes
2247 elabLocalToProject = isLocalToProject pkg
2248 elabBuildStyle =
2249 if shouldBuildInplaceOnly pkg
2250 then BuildInplaceOnly OnDisk
2251 else BuildAndInstall
2252 elabPackageDbs = projectConfigPackageDBs sharedPackageConfig
2253 elabBuildPackageDBStack = buildAndRegisterDbs
2254 elabRegisterPackageDBStack = buildAndRegisterDbs
2256 elabSetupScriptStyle = packageSetupScriptStyle elabPkgDescription
2257 elabSetupScriptCliVersion =
2258 packageSetupScriptSpecVersion
2259 elabSetupScriptStyle
2260 elabPkgDescription
2261 libDepGraph
2262 deps0
2263 elabSetupPackageDBStack = buildAndRegisterDbs
2265 elabInplaceBuildPackageDBStack = inplacePackageDbs
2266 elabInplaceRegisterPackageDBStack = inplacePackageDbs
2267 elabInplaceSetupPackageDBStack = inplacePackageDbs
2269 buildAndRegisterDbs
2270 | shouldBuildInplaceOnly pkg = inplacePackageDbs
2271 | otherwise = corePackageDbs
2273 elabPkgDescriptionOverride = descOverride
2275 elabBuildOptions =
2276 LBC.BuildOptions
2277 { withVanillaLib = perPkgOptionFlag pkgid True packageConfigVanillaLib -- TODO: [required feature]: also needs to be handled recursively
2278 , withSharedLib = canBuildSharedLibs && pkgid `Set.member` pkgsUseSharedLibrary
2279 , withStaticLib = perPkgOptionFlag pkgid False packageConfigStaticLib
2280 , withDynExe = perPkgOptionFlag pkgid False packageConfigDynExe
2281 , withFullyStaticExe = perPkgOptionFlag pkgid False packageConfigFullyStaticExe
2282 , withGHCiLib = perPkgOptionFlag pkgid False packageConfigGHCiLib -- TODO: [required feature] needs to default to enabled on windows still
2283 , withProfExe = perPkgOptionFlag pkgid False packageConfigProf
2284 , withProfLib = canBuildProfilingLibs && pkgid `Set.member` pkgsUseProfilingLibrary
2285 , withProfLibShared = canBuildProfilingSharedLibs && pkgid `Set.member` pkgsUseProfilingLibraryShared
2286 , exeCoverage = perPkgOptionFlag pkgid False packageConfigCoverage
2287 , libCoverage = perPkgOptionFlag pkgid False packageConfigCoverage
2288 , withOptimization = perPkgOptionFlag pkgid NormalOptimisation packageConfigOptimization
2289 , splitObjs = perPkgOptionFlag pkgid False packageConfigSplitObjs
2290 , splitSections = perPkgOptionFlag pkgid False packageConfigSplitSections
2291 , stripLibs = perPkgOptionFlag pkgid False packageConfigStripLibs
2292 , stripExes = perPkgOptionFlag pkgid False packageConfigStripExes
2293 , withDebugInfo = perPkgOptionFlag pkgid NoDebugInfo packageConfigDebugInfo
2294 , relocatable = perPkgOptionFlag pkgid False packageConfigRelocatable
2295 , withProfLibDetail = elabProfExeDetail
2296 , withProfExeDetail = elabProfLibDetail
2299 ( elabProfExeDetail
2300 , elabProfLibDetail
2302 perPkgOptionLibExeFlag
2303 pkgid
2304 ProfDetailDefault
2305 packageConfigProfDetail
2306 packageConfigProfLibDetail
2308 elabDumpBuildInfo = perPkgOptionFlag pkgid NoDumpBuildInfo packageConfigDumpBuildInfo
2310 -- Combine the configured compiler prog settings with the user-supplied
2311 -- config. For the compiler progs any user-supplied config was taken
2312 -- into account earlier when configuring the compiler so its ok that
2313 -- our configured settings for the compiler override the user-supplied
2314 -- config here.
2315 elabProgramPaths =
2316 Map.fromList
2317 [ (programId prog, programPath prog)
2318 | prog <- configuredPrograms compilerprogdb
2320 <> perPkgOptionMapLast pkgid packageConfigProgramPaths
2321 elabProgramArgs =
2322 Map.fromList
2323 [ (programId prog, args)
2324 | prog <- configuredPrograms compilerprogdb
2325 , let args = programOverrideArgs $ addHaddockIfDocumentationEnabled prog
2326 , not (null args)
2328 <> perPkgOptionMapMappend pkgid packageConfigProgramArgs
2329 elabProgramPathExtra = perPkgOptionNubList pkgid packageConfigProgramPathExtra
2330 elabConfigureScriptArgs = perPkgOptionList pkgid packageConfigConfigureArgs
2331 elabExtraLibDirs = perPkgOptionList pkgid packageConfigExtraLibDirs
2332 elabExtraLibDirsStatic = perPkgOptionList pkgid packageConfigExtraLibDirsStatic
2333 elabExtraFrameworkDirs = perPkgOptionList pkgid packageConfigExtraFrameworkDirs
2334 elabExtraIncludeDirs = perPkgOptionList pkgid packageConfigExtraIncludeDirs
2335 elabProgPrefix = perPkgOptionMaybe pkgid packageConfigProgPrefix
2336 elabProgSuffix = perPkgOptionMaybe pkgid packageConfigProgSuffix
2338 elabHaddockHoogle = perPkgOptionFlag pkgid False packageConfigHaddockHoogle
2339 elabHaddockHtml = perPkgOptionFlag pkgid False packageConfigHaddockHtml
2340 elabHaddockHtmlLocation = perPkgOptionMaybe pkgid packageConfigHaddockHtmlLocation
2341 elabHaddockForeignLibs = perPkgOptionFlag pkgid False packageConfigHaddockForeignLibs
2342 elabHaddockForHackage = perPkgOptionFlag pkgid Cabal.ForDevelopment packageConfigHaddockForHackage
2343 elabHaddockExecutables = perPkgOptionFlag pkgid False packageConfigHaddockExecutables
2344 elabHaddockTestSuites = perPkgOptionFlag pkgid False packageConfigHaddockTestSuites
2345 elabHaddockBenchmarks = perPkgOptionFlag pkgid False packageConfigHaddockBenchmarks
2346 elabHaddockInternal = perPkgOptionFlag pkgid False packageConfigHaddockInternal
2347 elabHaddockCss = perPkgOptionMaybe pkgid packageConfigHaddockCss
2348 elabHaddockLinkedSource = perPkgOptionFlag pkgid False packageConfigHaddockLinkedSource
2349 elabHaddockQuickJump = perPkgOptionFlag pkgid False packageConfigHaddockQuickJump
2350 elabHaddockHscolourCss = perPkgOptionMaybe pkgid packageConfigHaddockHscolourCss
2351 elabHaddockContents = perPkgOptionMaybe pkgid packageConfigHaddockContents
2352 elabHaddockIndex = perPkgOptionMaybe pkgid packageConfigHaddockIndex
2353 elabHaddockBaseUrl = perPkgOptionMaybe pkgid packageConfigHaddockBaseUrl
2354 elabHaddockResourcesDir = perPkgOptionMaybe pkgid packageConfigHaddockResourcesDir
2355 elabHaddockOutputDir = perPkgOptionMaybe pkgid packageConfigHaddockOutputDir
2356 elabHaddockUseUnicode = perPkgOptionFlag pkgid False packageConfigHaddockUseUnicode
2358 elabTestMachineLog = perPkgOptionMaybe pkgid packageConfigTestMachineLog
2359 elabTestHumanLog = perPkgOptionMaybe pkgid packageConfigTestHumanLog
2360 elabTestShowDetails = perPkgOptionMaybe pkgid packageConfigTestShowDetails
2361 elabTestKeepTix = perPkgOptionFlag pkgid False packageConfigTestKeepTix
2362 elabTestWrapper = perPkgOptionMaybe pkgid packageConfigTestWrapper
2363 elabTestFailWhenNoTestSuites = perPkgOptionFlag pkgid False packageConfigTestFailWhenNoTestSuites
2364 elabTestTestOptions = perPkgOptionList pkgid packageConfigTestTestOptions
2366 elabBenchmarkOptions = perPkgOptionList pkgid packageConfigBenchmarkOptions
2368 perPkgOptionFlag :: PackageId -> a -> (PackageConfig -> Flag a) -> a
2369 perPkgOptionMaybe :: PackageId -> (PackageConfig -> Flag a) -> Maybe a
2370 perPkgOptionList :: PackageId -> (PackageConfig -> [a]) -> [a]
2372 perPkgOptionFlag pkgid def f = fromFlagOrDefault def (lookupPerPkgOption pkgid f)
2373 perPkgOptionMaybe pkgid f = flagToMaybe (lookupPerPkgOption pkgid f)
2374 perPkgOptionList pkgid f = lookupPerPkgOption pkgid f
2375 perPkgOptionNubList pkgid f = fromNubList (lookupPerPkgOption pkgid f)
2376 perPkgOptionMapLast pkgid f = getMapLast (lookupPerPkgOption pkgid f)
2377 perPkgOptionMapMappend pkgid f = getMapMappend (lookupPerPkgOption pkgid f)
2379 perPkgOptionLibExeFlag pkgid def fboth flib = (exe, lib)
2380 where
2381 exe = fromFlagOrDefault def bothflag
2382 lib = fromFlagOrDefault def (bothflag <> libflag)
2384 bothflag = lookupPerPkgOption pkgid fboth
2385 libflag = lookupPerPkgOption pkgid flib
2387 lookupPerPkgOption
2388 :: (Package pkg, Monoid m)
2389 => pkg
2390 -> (PackageConfig -> m)
2391 -> m
2392 lookupPerPkgOption pkg f =
2393 -- This is where we merge the options from the project config that
2394 -- apply to all packages, all project local packages, and to specific
2395 -- named packages
2396 global `mappend` local `mappend` perpkg
2397 where
2398 global = f allPackagesConfig
2399 local
2400 | isLocalToProject pkg =
2401 f localPackagesConfig
2402 | otherwise =
2403 mempty
2404 perpkg = maybe mempty f (Map.lookup (packageName pkg) perPackageConfig)
2406 inplacePackageDbs =
2407 corePackageDbs
2408 ++ [distPackageDB (compilerId compiler)]
2410 corePackageDbs = storePackageDBStack compiler (projectConfigPackageDBs sharedPackageConfig)
2412 -- For this local build policy, every package that lives in a local source
2413 -- dir (as opposed to a tarball), or depends on such a package, will be
2414 -- built inplace into a shared dist dir. Tarball packages that depend on
2415 -- source dir packages will also get unpacked locally.
2416 shouldBuildInplaceOnly :: SolverPackage loc -> Bool
2417 shouldBuildInplaceOnly pkg =
2418 Set.member
2419 (packageId pkg)
2420 pkgsToBuildInplaceOnly
2422 pkgsToBuildInplaceOnly :: Set PackageId
2423 pkgsToBuildInplaceOnly =
2424 Set.fromList $
2425 map packageId $
2426 SolverInstallPlan.reverseDependencyClosure
2427 solverPlan
2428 (map PlannedId (Set.toList pkgsLocalToProject))
2430 isLocalToProject :: Package pkg => pkg -> Bool
2431 isLocalToProject pkg =
2432 Set.member
2433 (packageId pkg)
2434 pkgsLocalToProject
2436 pkgsLocalToProject :: Set PackageId
2437 pkgsLocalToProject =
2438 Set.fromList (catMaybes (map shouldBeLocal localPackages))
2439 -- TODO: localPackages is a misnomer, it's all project packages
2440 -- here is where we decide which ones will be local!
2442 pkgsUseSharedLibrary :: Set PackageId
2443 pkgsUseSharedLibrary =
2444 packagesWithLibDepsDownwardClosedProperty needsSharedLib
2446 needsSharedLib pkgid =
2447 fromMaybe
2448 compilerShouldUseSharedLibByDefault
2449 -- Case 1: --enable-shared or --disable-shared is passed explicitly, honour that.
2450 ( case pkgSharedLib of
2451 Just v -> Just v
2452 Nothing -> case pkgDynExe of
2453 -- case 2: If --enable-executable-dynamic is passed then turn on
2454 -- shared library generation.
2455 Just True ->
2456 -- Case 3: If --enable-profiling is passed, then we are going to
2457 -- build profiled dynamic, so no need for shared libraries.
2458 case pkgProf of
2459 Just True -> if canBuildProfilingSharedLibs then Nothing else Just True
2460 _ -> Just True
2461 -- But don't necessarily turn off shared library generation if
2462 -- --disable-executable-dynamic is passed. The shared objects might
2463 -- be needed for something different.
2464 _ -> Nothing
2466 where
2467 pkgSharedLib = perPkgOptionMaybe pkgid packageConfigSharedLib
2468 pkgDynExe = perPkgOptionMaybe pkgid packageConfigDynExe
2469 pkgProf = perPkgOptionMaybe pkgid packageConfigProf
2471 -- TODO: [code cleanup] move this into the Cabal lib. It's currently open
2472 -- coded in Distribution.Simple.Configure, but should be made a proper
2473 -- function of the Compiler or CompilerInfo.
2474 compilerShouldUseSharedLibByDefault =
2475 case compilerFlavor compiler of
2476 GHC -> GHC.compilerBuildWay compiler == DynWay && canBuildSharedLibs
2477 GHCJS -> GHCJS.isDynamic compiler
2478 _ -> False
2480 compilerShouldUseProfilingLibByDefault =
2481 case compilerFlavor compiler of
2482 GHC -> GHC.compilerBuildWay compiler == ProfWay && canBuildProfilingLibs
2483 _ -> False
2485 compilerShouldUseProfilingSharedLibByDefault =
2486 case compilerFlavor compiler of
2487 GHC -> GHC.compilerBuildWay compiler == ProfDynWay && canBuildProfilingSharedLibs
2488 _ -> False
2490 -- Returns False if we definitely can't build shared libs
2491 canBuildWayLibs predicate = case predicate compiler of
2492 Just can_build -> can_build
2493 -- If we don't know for certain, just assume we can
2494 -- which matches behaviour in previous cabal releases
2495 Nothing -> True
2497 canBuildSharedLibs = canBuildWayLibs dynamicSupported
2498 canBuildProfilingLibs = canBuildWayLibs profilingVanillaSupported
2499 canBuildProfilingSharedLibs = canBuildWayLibs profilingDynamicSupported
2501 wayWarnings pkg = do
2502 when
2503 (needsProfilingLib pkg && not canBuildProfilingLibs)
2504 (warnProgress (text "Compiler does not support building p libraries, profiling is disabled"))
2505 when
2506 (needsSharedLib pkg && not canBuildSharedLibs)
2507 (warnProgress (text "Compiler does not support building dyn libraries, dynamic libraries are disabled"))
2508 when
2509 (needsProfilingLibShared pkg && not canBuildProfilingSharedLibs)
2510 (warnProgress (text "Compiler does not support building p_dyn libraries, profiling dynamic libraries are disabled."))
2512 pkgsUseProfilingLibrary :: Set PackageId
2513 pkgsUseProfilingLibrary =
2514 packagesWithLibDepsDownwardClosedProperty needsProfilingLib
2516 needsProfilingLib pkg =
2517 fromFlagOrDefault compilerShouldUseProfilingLibByDefault (profBothFlag <> profLibFlag)
2518 where
2519 pkgid = packageId pkg
2520 profBothFlag = lookupPerPkgOption pkgid packageConfigProf
2521 profLibFlag = lookupPerPkgOption pkgid packageConfigProfLib
2523 pkgsUseProfilingLibraryShared :: Set PackageId
2524 pkgsUseProfilingLibraryShared =
2525 packagesWithLibDepsDownwardClosedProperty needsProfilingLibShared
2527 needsProfilingLibShared pkg =
2528 fromMaybe
2529 compilerShouldUseProfilingSharedLibByDefault
2530 -- case 1: If --enable-profiling-shared is passed explicitly, honour that
2531 ( case profLibSharedFlag of
2532 Just v -> Just v
2533 Nothing -> case pkgDynExe of
2534 Just True ->
2535 case pkgProf of
2536 -- case 2: --enable-executable-dynamic + --enable-profiling
2537 -- turn on shared profiling libraries
2538 Just True -> if canBuildProfilingSharedLibs then Just True else Nothing
2539 _ -> Nothing
2540 -- But don't necessarily turn off shared library generation is
2541 -- --disable-executable-dynamic is passed. The shared objects might
2542 -- be needed for something different.
2543 _ -> Nothing
2545 where
2546 pkgid = packageId pkg
2547 profLibSharedFlag = perPkgOptionMaybe pkgid packageConfigProfShared
2548 pkgDynExe = perPkgOptionMaybe pkgid packageConfigDynExe
2549 pkgProf = perPkgOptionMaybe pkgid packageConfigProf
2551 -- TODO: [code cleanup] unused: the old deprecated packageConfigProfExe
2553 libDepGraph =
2554 Graph.fromDistinctList $
2556 NonSetupLibDepSolverPlanPackage
2557 (SolverInstallPlan.toList solverPlan)
2559 packagesWithLibDepsDownwardClosedProperty property =
2560 Set.fromList
2561 . map packageId
2562 . fromMaybe []
2563 $ Graph.closure
2564 libDepGraph
2565 [ Graph.nodeKey pkg
2566 | pkg <- SolverInstallPlan.toList solverPlan
2567 , property (packageId pkg) -- just the packages that satisfy the property
2568 -- TODO: [nice to have] this does not check the config consistency,
2569 -- e.g. a package explicitly turning off profiling, but something
2570 -- depending on it that needs profiling. This really needs a separate
2571 -- package config validation/resolution pass.
2574 -- TODO: [nice to have] config consistency checking:
2575 -- + profiling libs & exes, exe needs lib, recursive
2576 -- + shared libs & exes, exe needs lib, recursive
2577 -- + vanilla libs & exes, exe needs lib, recursive
2578 -- + ghci or shared lib needed by TH, recursive, ghc version dependent
2580 -- TODO: Drop matchPlanPkg/matchElabPkg in favor of mkCCMapping
2582 shouldBeLocal :: PackageSpecifier (SourcePackage (PackageLocation loc)) -> Maybe PackageId
2583 shouldBeLocal NamedPackage{} = Nothing
2584 shouldBeLocal (SpecificSourcePackage pkg) = case srcpkgSource pkg of
2585 LocalUnpackedPackage _ -> Just (packageId pkg)
2586 _ -> Nothing
2588 -- | Given a 'ElaboratedPlanPackage', report if it matches a 'ComponentName'.
2589 matchPlanPkg :: (ComponentName -> Bool) -> ElaboratedPlanPackage -> Bool
2590 matchPlanPkg p = InstallPlan.foldPlanPackage (p . ipiComponentName) (matchElabPkg p)
2592 -- | Get the appropriate 'ComponentName' which identifies an installed
2593 -- component.
2594 ipiComponentName :: IPI.InstalledPackageInfo -> ComponentName
2595 ipiComponentName = CLibName . IPI.sourceLibName
2597 -- | Given a 'ElaboratedConfiguredPackage', report if it matches a
2598 -- 'ComponentName'.
2599 matchElabPkg :: (ComponentName -> Bool) -> ElaboratedConfiguredPackage -> Bool
2600 matchElabPkg p elab =
2601 case elabPkgOrComp elab of
2602 ElabComponent comp -> maybe False p (compComponentName comp)
2603 ElabPackage _ ->
2604 -- So, what should we do here? One possibility is to
2605 -- unconditionally return 'True', because whatever it is
2606 -- that we're looking for, it better be in this package.
2607 -- But this is a bit dodgy if the package doesn't actually
2608 -- have, e.g., a library. Fortunately, it's not possible
2609 -- for the build of the library/executables to be toggled
2610 -- by 'pkgStanzasEnabled', so the only thing we have to
2611 -- test is if the component in question is *buildable.*
2613 (p . componentName)
2614 (Cabal.pkgBuildableComponents (elabPkgDescription elab))
2616 -- | Given an 'ElaboratedPlanPackage', generate the mapping from 'PackageName'
2617 -- and 'ComponentName' to the 'ComponentId' that should be used
2618 -- in this case.
2619 mkCCMapping
2620 :: ElaboratedPlanPackage
2621 -> (PackageName, Map ComponentName (AnnotatedId ComponentId))
2622 mkCCMapping =
2623 InstallPlan.foldPlanPackage
2624 ( \ipkg ->
2625 ( packageName ipkg
2626 , Map.singleton
2627 (ipiComponentName ipkg)
2628 -- TODO: libify
2629 ( AnnotatedId
2630 { ann_id = IPI.installedComponentId ipkg
2631 , ann_pid = packageId ipkg
2632 , ann_cname = IPI.sourceComponentName ipkg
2637 $ \elab ->
2638 let mk_aid cn =
2639 AnnotatedId
2640 { ann_id = elabComponentId elab
2641 , ann_pid = packageId elab
2642 , ann_cname = cn
2644 in ( packageName elab
2645 , case elabPkgOrComp elab of
2646 ElabComponent comp ->
2647 case compComponentName comp of
2648 Nothing -> Map.empty
2649 Just n -> Map.singleton n (mk_aid n)
2650 ElabPackage _ ->
2651 Map.fromList $
2653 (\comp -> let cn = Cabal.componentName comp in (cn, mk_aid cn))
2654 (Cabal.pkgBuildableComponents (elabPkgDescription elab))
2657 -- | Given an 'ElaboratedPlanPackage', generate the mapping from 'ComponentId'
2658 -- to the shape of this package, as per mix-in linking.
2659 mkShapeMapping
2660 :: ElaboratedPlanPackage
2661 -> (ComponentId, (OpenUnitId, ModuleShape))
2662 mkShapeMapping dpkg =
2663 (getComponentId dpkg, (indef_uid, shape))
2664 where
2665 (dcid, shape) =
2666 InstallPlan.foldPlanPackage
2667 -- Uses Monad (->)
2668 (liftM2 (,) IPI.installedComponentId shapeInstalledPackage)
2669 (liftM2 (,) elabComponentId elabModuleShape)
2670 dpkg
2671 indef_uid =
2672 IndefFullUnitId
2673 dcid
2674 ( Map.fromList
2675 [ (req, OpenModuleVar req)
2676 | req <- Set.toList (modShapeRequires shape)
2680 -- | Get the bin\/ directories that a package's executables should reside in.
2682 -- The result may be empty if the package does not build any executables.
2684 -- The result may have several entries if this is an inplace build of a package
2685 -- with multiple executables.
2686 binDirectories
2687 :: DistDirLayout
2688 -> ElaboratedSharedConfig
2689 -> ElaboratedConfiguredPackage
2690 -> [FilePath]
2691 binDirectories layout config package = case elabBuildStyle package of
2692 -- quick sanity check: no sense returning a bin directory if we're not going
2693 -- to put any executables in it, that will just clog up the PATH
2694 _ | noExecutables -> []
2695 BuildAndInstall -> [installedBinDirectory package]
2696 BuildInplaceOnly{} -> map (root </>) $ case elabPkgOrComp package of
2697 ElabComponent comp -> case compSolverName comp of
2698 CD.ComponentExe n -> [prettyShow n]
2699 _ -> []
2700 ElabPackage _ ->
2701 map (prettyShow . PD.exeName)
2702 . PD.executables
2703 . elabPkgDescription
2704 $ package
2705 where
2706 noExecutables = null . PD.executables . elabPkgDescription $ package
2707 root =
2708 distBuildDirectory layout (elabDistDirParams config package)
2709 </> "build"
2711 type InstS = Map UnitId ElaboratedPlanPackage
2712 type InstM a = State InstS a
2714 getComponentId
2715 :: ElaboratedPlanPackage
2716 -> ComponentId
2717 getComponentId (InstallPlan.PreExisting dipkg) = IPI.installedComponentId dipkg
2718 getComponentId (InstallPlan.Configured elab) = elabComponentId elab
2719 getComponentId (InstallPlan.Installed elab) = elabComponentId elab
2721 extractElabBuildStyle
2722 :: InstallPlan.GenericPlanPackage ipkg ElaboratedConfiguredPackage
2723 -> BuildStyle
2724 extractElabBuildStyle (InstallPlan.Configured elab) = elabBuildStyle elab
2725 extractElabBuildStyle _ = BuildAndInstall
2727 -- instantiateInstallPlan is responsible for filling out an InstallPlan
2728 -- with all of the extra Configured packages that would be generated by
2729 -- recursively instantiating the dependencies of packages.
2731 -- Suppose we are compiling the following packages:
2733 -- unit f where
2734 -- signature H
2736 -- unit g where
2737 -- dependency f[H=containers:Data.Map]
2739 -- At entry, we have an InstallPlan with a single plan package per
2740 -- actual source package, e.g., only (indefinite!) f and g. The job of
2741 -- instantiation is to turn this into three plan packages: each of the
2742 -- packages as before, but also a new, definite package f[H=containers:Data.Map]
2744 -- How do we do this? The general strategy is to iterate over every
2745 -- package in the existing plan and recursively create new entries for
2746 -- each of its dependencies which is an instantiated package (e.g.,
2747 -- f[H=p:G]). This process must be recursive, as f itself may depend on
2748 -- OTHER packages which it instantiated using its hole H.
2750 -- Some subtleties:
2752 -- * We have to keep track of whether or not we are instantiating with
2753 -- inplace packages, because instantiating a non-inplace package with
2754 -- an inplace packages makes it inplace (since it depends on
2755 -- something in the inplace store)! The rule is that if any of the
2756 -- modules in an instantiation are inplace, then the instantiated
2757 -- unit itself must be inplace. There is then a bunch of faffing
2758 -- about to keep track of BuildStyle.
2760 -- * ElaboratedConfiguredPackage was never really designed for post
2761 -- facto instantiation, so some of the steps for generating new
2762 -- instantiations are a little fraught. For example, the act of
2763 -- flipping a package to be inplace involves faffing about with four
2764 -- fields, because these fields are precomputed. A good refactor
2765 -- would be to reduce the amount of precomputation to simplify the
2766 -- algorithm here.
2768 -- * We use the state monad to cache already instantiated modules, so
2769 -- we don't instantiate the same thing multiple times.
2771 instantiateInstallPlan :: StoreDirLayout -> InstallDirs.InstallDirTemplates -> ElaboratedSharedConfig -> ElaboratedInstallPlan -> ElaboratedInstallPlan
2772 instantiateInstallPlan storeDirLayout defaultInstallDirs elaboratedShared plan =
2773 InstallPlan.new
2774 (IndependentGoals False)
2775 (Graph.fromDistinctList (Map.elems ready_map))
2776 where
2777 pkgs = InstallPlan.toList plan
2779 cmap = Map.fromList [(getComponentId pkg, pkg) | pkg <- pkgs]
2781 instantiateUnitId
2782 :: ComponentId
2783 -> Map ModuleName (Module, BuildStyle)
2784 -> InstM (DefUnitId, BuildStyle)
2785 instantiateUnitId cid insts = state $ \s ->
2786 case Map.lookup uid s of
2787 Nothing ->
2788 -- Knot tied
2789 -- TODO: I don't think the knot tying actually does
2790 -- anything useful
2791 let (r, s') =
2792 runState
2793 (instantiateComponent uid cid insts)
2794 (Map.insert uid r s)
2795 in ((def_uid, extractElabBuildStyle r), Map.insert uid r s')
2796 Just r -> ((def_uid, extractElabBuildStyle r), s)
2797 where
2798 def_uid = mkDefUnitId cid (fmap fst insts)
2799 uid = unDefUnitId def_uid
2801 -- No need to InplaceT; the inplace-ness is properly computed for
2802 -- the ElaboratedPlanPackage, so that will implicitly pass it on
2803 instantiateComponent
2804 :: UnitId
2805 -> ComponentId
2806 -> Map ModuleName (Module, BuildStyle)
2807 -> InstM ElaboratedPlanPackage
2808 instantiateComponent uid cid insts
2809 | Just planpkg <- Map.lookup cid cmap =
2810 case planpkg of
2811 InstallPlan.Configured
2812 ( elab0@ElaboratedConfiguredPackage
2813 { elabPkgOrComp = ElabComponent comp
2815 ) -> do
2816 deps <-
2817 traverse (fmap fst . substUnitId insts) (compLinkedLibDependencies comp)
2818 let build_style = fold (fmap snd insts)
2819 let getDep (Module dep_uid _) = [dep_uid]
2820 elab1 =
2821 fixupBuildStyle build_style $
2822 elab0
2823 { elabUnitId = uid
2824 , elabComponentId = cid
2825 , elabInstantiatedWith = fmap fst insts
2826 , elabIsCanonical = Map.null (fmap fst insts)
2827 , elabPkgOrComp =
2828 ElabComponent
2829 comp
2830 { compOrderLibDependencies =
2831 (if Map.null insts then [] else [newSimpleUnitId cid])
2832 ++ ordNub
2833 ( map
2834 unDefUnitId
2835 (deps ++ concatMap (getDep . fst) (Map.elems insts))
2839 elab =
2840 elab1
2841 { elabInstallDirs =
2842 computeInstallDirs
2843 storeDirLayout
2844 defaultInstallDirs
2845 elaboratedShared
2846 elab1
2848 return $ InstallPlan.Configured elab
2849 _ -> return planpkg
2850 | otherwise = error ("instantiateComponent: " ++ prettyShow cid)
2852 substUnitId :: Map ModuleName (Module, BuildStyle) -> OpenUnitId -> InstM (DefUnitId, BuildStyle)
2853 substUnitId _ (DefiniteUnitId uid) =
2854 -- This COULD actually, secretly, be an inplace package, but in
2855 -- that case it doesn't matter as it's already been recorded
2856 -- in the package that depends on this
2857 return (uid, BuildAndInstall)
2858 substUnitId subst (IndefFullUnitId cid insts) = do
2859 insts' <- substSubst subst insts
2860 instantiateUnitId cid insts'
2862 -- NB: NOT composition
2863 substSubst
2864 :: Map ModuleName (Module, BuildStyle)
2865 -> Map ModuleName OpenModule
2866 -> InstM (Map ModuleName (Module, BuildStyle))
2867 substSubst subst insts = traverse (substModule subst) insts
2869 substModule :: Map ModuleName (Module, BuildStyle) -> OpenModule -> InstM (Module, BuildStyle)
2870 substModule subst (OpenModuleVar mod_name)
2871 | Just m <- Map.lookup mod_name subst = return m
2872 | otherwise = error "substModule: non-closing substitution"
2873 substModule subst (OpenModule uid mod_name) = do
2874 (uid', build_style) <- substUnitId subst uid
2875 return (Module uid' mod_name, build_style)
2877 indefiniteUnitId :: ComponentId -> InstM UnitId
2878 indefiniteUnitId cid = do
2879 let uid = newSimpleUnitId cid
2880 r <- indefiniteComponent uid cid
2881 state $ \s -> (uid, Map.insert uid r s)
2883 indefiniteComponent :: UnitId -> ComponentId -> InstM ElaboratedPlanPackage
2884 indefiniteComponent _uid cid
2885 -- Only need Configured; this phase happens before improvement, so
2886 -- there shouldn't be any Installed packages here.
2887 | Just (InstallPlan.Configured epkg) <- Map.lookup cid cmap
2888 , ElabComponent elab_comp <- elabPkgOrComp epkg =
2890 -- We need to do a little more processing of the includes: some
2891 -- of them are fully definite even without substitution. We
2892 -- want to build those too; see #5634.
2894 -- This code mimics similar code in Distribution.Backpack.ReadyComponent;
2895 -- however, unlike the conversion from LinkedComponent to
2896 -- ReadyComponent, this transformation is done *without*
2897 -- changing the type in question; and what we are simply
2898 -- doing is enforcing tighter invariants on the data
2899 -- structure in question. The new invariant is that there
2900 -- is no IndefFullUnitId in compLinkedLibDependencies that actually
2901 -- has no holes. We couldn't specify this invariant when
2902 -- we initially created the ElaboratedPlanPackage because
2903 -- we have no way of actually reifying the UnitId into a
2904 -- DefiniteUnitId (that's what substUnitId does!)
2905 new_deps <- for (compLinkedLibDependencies elab_comp) $ \uid ->
2906 if Set.null (openUnitIdFreeHoles uid)
2907 then fmap (DefiniteUnitId . fst) (substUnitId Map.empty uid)
2908 else return uid
2909 -- NB: no fixupBuildStyle needed here, as if the indefinite
2910 -- component depends on any inplace packages, it itself must
2911 -- be indefinite! There is no substitution here, we can't
2912 -- post facto add inplace deps
2913 return . InstallPlan.Configured $
2914 epkg
2915 { elabPkgOrComp =
2916 ElabComponent
2917 elab_comp
2918 { compLinkedLibDependencies = new_deps
2919 , -- I think this is right: any new definite unit ids we
2920 -- minted in the phase above need to be built before us.
2921 -- Add 'em in. This doesn't remove any old dependencies
2922 -- on the indefinite package; they're harmless.
2923 compOrderLibDependencies =
2924 ordNub $
2925 compOrderLibDependencies elab_comp
2926 ++ [unDefUnitId d | DefiniteUnitId d <- new_deps]
2929 | Just planpkg <- Map.lookup cid cmap =
2930 return planpkg
2931 | otherwise = error ("indefiniteComponent: " ++ prettyShow cid)
2933 fixupBuildStyle BuildAndInstall elab = elab
2934 fixupBuildStyle _ (elab@ElaboratedConfiguredPackage{elabBuildStyle = BuildInplaceOnly{}}) = elab
2935 fixupBuildStyle t@(BuildInplaceOnly{}) elab =
2936 elab
2937 { elabBuildStyle = t
2938 , elabBuildPackageDBStack = elabInplaceBuildPackageDBStack elab
2939 , elabRegisterPackageDBStack = elabInplaceRegisterPackageDBStack elab
2940 , elabSetupPackageDBStack = elabInplaceSetupPackageDBStack elab
2943 ready_map = execState work Map.empty
2945 work = for_ pkgs $ \pkg ->
2946 case pkg of
2947 InstallPlan.Configured elab
2948 | not (Map.null (elabLinkedInstantiatedWith elab)) ->
2949 indefiniteUnitId (elabComponentId elab)
2950 >> return ()
2951 _ ->
2952 instantiateUnitId (getComponentId pkg) Map.empty
2953 >> return ()
2955 ---------------------------
2956 -- Build targets
2959 -- Refer to ProjectPlanning.Types for details of these important types:
2961 -- data ComponentTarget = ...
2962 -- data SubComponentTarget = ...
2964 -- One step in the build system is to translate higher level intentions like
2965 -- "build this package", "test that package", or "repl that component" into
2966 -- a more detailed specification of exactly which components to build (or other
2967 -- actions like repl or build docs). This translation is somewhat different for
2968 -- different commands. For example "test" for a package will build a different
2969 -- set of components than "build". In addition, the translation of these
2970 -- intentions can fail. For example "run" for a package is only unambiguous
2971 -- when the package has a single executable.
2973 -- So we need a little bit of infrastructure to make it easy for the command
2974 -- implementations to select what component targets are meant when a user asks
2975 -- to do something with a package or component. To do this (and to be able to
2976 -- produce good error messages for mistakes and when targets are not available)
2977 -- we need to gather and summarise accurate information about all the possible
2978 -- targets, both available and unavailable. Then a command implementation can
2979 -- decide which of the available component targets should be selected.
2981 -- | An available target represents a component within a package that a user
2982 -- command could plausibly refer to. In this sense, all the components defined
2983 -- within the package are things the user could refer to, whether or not it
2984 -- would actually be possible to build that component.
2986 -- In particular the available target contains an 'AvailableTargetStatus' which
2987 -- informs us about whether it's actually possible to select this component to
2988 -- be built, and if not why not. This detail makes it possible for command
2989 -- implementations (like @build@, @test@ etc) to accurately report why a target
2990 -- cannot be used.
2992 -- Note that the type parameter is used to help enforce that command
2993 -- implementations can only select targets that can actually be built (by
2994 -- forcing them to return the @k@ value for the selected targets).
2995 -- In particular 'resolveTargets' makes use of this (with @k@ as
2996 -- @('UnitId', ComponentName')@) to identify the targets thus selected.
2997 data AvailableTarget k = AvailableTarget
2998 { availableTargetPackageId :: PackageId
2999 , availableTargetComponentName :: ComponentName
3000 , availableTargetStatus :: AvailableTargetStatus k
3001 , availableTargetLocalToProject :: Bool
3003 deriving (Eq, Show, Functor)
3005 -- | The status of a an 'AvailableTarget' component. This tells us whether
3006 -- it's actually possible to select this component to be built, and if not
3007 -- why not.
3008 data AvailableTargetStatus k
3009 = -- | When the user does @tests: False@
3010 TargetDisabledByUser
3011 | -- | When the solver could not enable tests
3012 TargetDisabledBySolver
3013 | -- | When the component has @buildable: False@
3014 TargetNotBuildable
3015 | -- | When the component is non-core in a non-local package
3016 TargetNotLocal
3017 | -- | The target can or should be built
3018 TargetBuildable k TargetRequested
3019 deriving (Eq, Ord, Show, Functor)
3021 -- | This tells us whether a target ought to be built by default, or only if
3022 -- specifically requested. The policy is that components like libraries and
3023 -- executables are built by default by @build@, but test suites and benchmarks
3024 -- are not, unless this is overridden in the project configuration.
3025 data TargetRequested
3026 = -- | To be built by default
3027 TargetRequestedByDefault
3028 | -- | Not to be built by default
3029 TargetNotRequestedByDefault
3030 deriving (Eq, Ord, Show)
3032 -- | Given the install plan, produce the set of 'AvailableTarget's for each
3033 -- package-component pair.
3035 -- Typically there will only be one such target for each component, but for
3036 -- example if we have a plan with both normal and profiling variants of a
3037 -- component then we would get both as available targets, or similarly if we
3038 -- had a plan that contained two instances of the same version of a package.
3039 -- This approach makes it relatively easy to select all instances\/variants
3040 -- of a component.
3041 availableTargets
3042 :: ElaboratedInstallPlan
3043 -> Map
3044 (PackageId, ComponentName)
3045 [AvailableTarget (UnitId, ComponentName)]
3046 availableTargets installPlan =
3047 let rs =
3048 [ (pkgid, cname, fake, target)
3049 | pkg <- InstallPlan.toList installPlan
3050 , (pkgid, cname, fake, target) <- case pkg of
3051 InstallPlan.PreExisting ipkg -> availableInstalledTargets ipkg
3052 InstallPlan.Installed elab -> availableSourceTargets elab
3053 InstallPlan.Configured elab -> availableSourceTargets elab
3055 in Map.union
3056 ( Map.fromListWith
3057 (++)
3058 [ ((pkgid, cname), [target])
3059 | (pkgid, cname, fake, target) <- rs
3060 , not fake
3063 ( Map.fromList
3064 [ ((pkgid, cname), [target])
3065 | (pkgid, cname, fake, target) <- rs
3066 , fake
3070 -- The normal targets mask the fake ones. We get all instances of the
3071 -- normal ones and only one copy of the fake ones (as there are many
3072 -- duplicates of the fake ones). See 'availableSourceTargets' below for
3073 -- more details on this fake stuff is about.
3075 availableInstalledTargets
3076 :: IPI.InstalledPackageInfo
3077 -> [ ( PackageId
3078 , ComponentName
3079 , Bool
3080 , AvailableTarget (UnitId, ComponentName)
3083 availableInstalledTargets ipkg =
3084 let unitid = installedUnitId ipkg
3085 cname = CLibName LMainLibName
3086 status = TargetBuildable (unitid, cname) TargetRequestedByDefault
3087 target = AvailableTarget (packageId ipkg) cname status False
3088 fake = False
3089 in [(packageId ipkg, cname, fake, target)]
3091 availableSourceTargets
3092 :: ElaboratedConfiguredPackage
3093 -> [ ( PackageId
3094 , ComponentName
3095 , Bool
3096 , AvailableTarget (UnitId, ComponentName)
3099 availableSourceTargets elab =
3100 -- We have a somewhat awkward problem here. We need to know /all/ the
3101 -- components from /all/ the packages because these are the things that
3102 -- users could refer to. Unfortunately, at this stage the elaborated install
3103 -- plan does /not/ contain all components: some components have already
3104 -- been deleted because they cannot possibly be built. This is the case
3105 -- for components that are marked @buildable: False@ in their .cabal files.
3106 -- (It's not unreasonable that the unbuildable components have been pruned
3107 -- as the plan invariant is considerably simpler if all nodes can be built)
3109 -- We can recover the missing components but it's not exactly elegant. For
3110 -- a graph node corresponding to a component we still have the information
3111 -- about the package that it came from, and this includes the names of
3112 -- /all/ the other components in the package. So in principle this lets us
3113 -- find the names of all components, plus full details of the buildable
3114 -- components.
3116 -- Consider for example a package with 3 exe components: foo, bar and baz
3117 -- where foo and bar are buildable, but baz is not. So the plan contains
3118 -- nodes for the components foo and bar. Now we look at each of these two
3119 -- nodes and look at the package they come from and the names of the
3120 -- components in this package. This will give us the names foo, bar and
3121 -- baz, twice (once for each of the two buildable components foo and bar).
3123 -- We refer to these reconstructed missing components as fake targets.
3124 -- It is an invariant that they are not available to be built.
3126 -- To produce the final set of targets we put the fake targets in a finite
3127 -- map (thus eliminating the duplicates) and then we overlay that map with
3128 -- the normal buildable targets. (This is done above in 'availableTargets'.)
3130 [ (packageId elab, cname, fake, target)
3131 | component <- pkgComponents (elabPkgDescription elab)
3132 , let cname = componentName component
3133 status = componentAvailableTargetStatus component
3134 target =
3135 AvailableTarget
3136 { availableTargetPackageId = packageId elab
3137 , availableTargetComponentName = cname
3138 , availableTargetStatus = status
3139 , availableTargetLocalToProject = elabLocalToProject elab
3141 fake = isFakeTarget cname
3142 , -- TODO: The goal of this test is to exclude "instantiated"
3143 -- packages as available targets. This means that you can't
3144 -- ask for a particular instantiated component to be built;
3145 -- it will only get built by a dependency. Perhaps the
3146 -- correct way to implement this is to run selection
3147 -- prior to instantiating packages. If you refactor
3148 -- this, then you can delete this test.
3149 elabIsCanonical elab
3150 , -- Filter out some bogus parts of the cross product that are never needed
3151 case status of
3152 TargetBuildable{} | fake -> False
3153 _ -> True
3155 where
3156 isFakeTarget cname =
3157 case elabPkgOrComp elab of
3158 ElabPackage _ -> False
3159 ElabComponent elabComponent ->
3160 compComponentName elabComponent
3161 /= Just cname
3163 componentAvailableTargetStatus
3164 :: Component -> AvailableTargetStatus (UnitId, ComponentName)
3165 componentAvailableTargetStatus component =
3166 case componentOptionalStanza $ CD.componentNameToComponent cname of
3167 -- it is not an optional stanza, so a library, exe or foreign lib
3168 Nothing
3169 | not buildable -> TargetNotBuildable
3170 | otherwise ->
3171 TargetBuildable
3172 (elabUnitId elab, cname)
3173 TargetRequestedByDefault
3174 -- it is not an optional stanza, so a testsuite or benchmark
3175 Just stanza ->
3176 case ( optStanzaLookup stanza (elabStanzasRequested elab) -- TODO
3177 , optStanzaSetMember stanza (elabStanzasAvailable elab)
3178 ) of
3179 _ | not withinPlan -> TargetNotLocal
3180 (Just False, _) -> TargetDisabledByUser
3181 (Nothing, False) -> TargetDisabledBySolver
3182 _ | not buildable -> TargetNotBuildable
3183 (Just True, True) ->
3184 TargetBuildable
3185 (elabUnitId elab, cname)
3186 TargetRequestedByDefault
3187 (Nothing, True) ->
3188 TargetBuildable
3189 (elabUnitId elab, cname)
3190 TargetNotRequestedByDefault
3191 (Just True, False) ->
3192 error $ "componentAvailableTargetStatus: impossible; cname=" ++ prettyShow cname
3193 where
3194 cname = componentName component
3195 buildable = PD.buildable (componentBuildInfo component)
3196 withinPlan =
3197 elabLocalToProject elab
3198 || case elabPkgOrComp elab of
3199 ElabComponent elabComponent ->
3200 compComponentName elabComponent == Just cname
3201 ElabPackage _ ->
3202 case componentName component of
3203 CLibName (LMainLibName) -> True
3204 CExeName _ -> True
3205 -- TODO: what about sub-libs and foreign libs?
3206 _ -> False
3208 -- | Merge component targets that overlap each other. Specially when we have
3209 -- multiple targets for the same component and one of them refers to the whole
3210 -- component (rather than a module or file within) then all the other targets
3211 -- for that component are subsumed.
3213 -- We also allow for information associated with each component target, and
3214 -- whenever we targets subsume each other we aggregate their associated info.
3215 nubComponentTargets :: [(ComponentTarget, a)] -> [(ComponentTarget, NonEmpty a)]
3216 nubComponentTargets =
3217 concatMap (wholeComponentOverrides . map snd)
3218 . groupBy ((==) `on` fst)
3219 . sortBy (compare `on` fst)
3220 . map (\t@((ComponentTarget cname _, _)) -> (cname, t))
3221 . map compatSubComponentTargets
3222 where
3223 -- If we're building the whole component then that the only target all we
3224 -- need, otherwise we can have several targets within the component.
3225 wholeComponentOverrides
3226 :: [(ComponentTarget, a)]
3227 -> [(ComponentTarget, NonEmpty a)]
3228 wholeComponentOverrides ts =
3229 case [ta | ta@(ComponentTarget _ WholeComponent, _) <- ts] of
3230 ((t, x) : _) ->
3232 -- Delete tuple (t, x) from original list to avoid duplicates.
3233 -- Use 'deleteBy', to avoid additional Class constraint on 'nubComponentTargets'.
3234 ts' = deleteBy (\(t1, _) (t2, _) -> t1 == t2) (t, x) ts
3236 [(t, x :| map snd ts')]
3237 [] -> [(t, x :| []) | (t, x) <- ts]
3239 -- Not all Cabal Setup.hs versions support sub-component targets, so switch
3240 -- them over to the whole component
3241 compatSubComponentTargets :: (ComponentTarget, a) -> (ComponentTarget, a)
3242 compatSubComponentTargets target@(ComponentTarget cname _subtarget, x)
3243 | not setupHsSupportsSubComponentTargets =
3244 (ComponentTarget cname WholeComponent, x)
3245 | otherwise = target
3247 -- Actually the reality is that no current version of Cabal's Setup.hs
3248 -- build command actually support building specific files or modules.
3249 setupHsSupportsSubComponentTargets = False
3251 -- TODO: when that changes, adjust this test, e.g.
3252 -- \| pkgSetupScriptCliVersion >= Version [x,y] []
3254 pkgHasEphemeralBuildTargets :: ElaboratedConfiguredPackage -> Bool
3255 pkgHasEphemeralBuildTargets elab =
3256 (not . null) (elabReplTarget elab)
3257 || (not . null) (elabTestTargets elab)
3258 || (not . null) (elabBenchTargets elab)
3259 || (not . null) (elabHaddockTargets elab)
3260 || (not . null)
3261 [ () | ComponentTarget _ subtarget <- elabBuildTargets elab, subtarget /= WholeComponent
3264 -- | The components that we'll build all of, meaning that after they're built
3265 -- we can skip building them again (unlike with building just some modules or
3266 -- other files within a component).
3267 elabBuildTargetWholeComponents
3268 :: ElaboratedConfiguredPackage
3269 -> Set ComponentName
3270 elabBuildTargetWholeComponents elab =
3271 Set.fromList
3272 [cname | ComponentTarget cname WholeComponent <- elabBuildTargets elab]
3274 ------------------------------------------------------------------------------
3276 -- * Install plan pruning
3278 ------------------------------------------------------------------------------
3280 -- | How 'pruneInstallPlanToTargets' should interpret the per-package
3281 -- 'ComponentTarget's: as build, repl or haddock targets.
3282 data TargetAction
3283 = TargetActionConfigure
3284 | TargetActionBuild
3285 | TargetActionRepl
3286 | TargetActionTest
3287 | TargetActionBench
3288 | TargetActionHaddock
3290 -- | Given a set of per-package\/per-component targets, take the subset of the
3291 -- install plan needed to build those targets. Also, update the package config
3292 -- to specify which optional stanzas to enable, and which targets within each
3293 -- package to build.
3295 -- NB: Pruning happens after improvement, which is important because we
3296 -- will prune differently depending on what is already installed (to
3297 -- implement "sticky" test suite enabling behavior).
3298 pruneInstallPlanToTargets
3299 :: TargetAction
3300 -> Map UnitId [ComponentTarget]
3301 -> ElaboratedInstallPlan
3302 -> ElaboratedInstallPlan
3303 pruneInstallPlanToTargets targetActionType perPkgTargetsMap elaboratedPlan =
3304 InstallPlan.new (InstallPlan.planIndepGoals elaboratedPlan)
3305 . Graph.fromDistinctList
3306 -- We have to do the pruning in two passes
3307 . pruneInstallPlanPass2
3308 . pruneInstallPlanPass1
3309 -- Set the targets that will be the roots for pruning
3310 . setRootTargets targetActionType perPkgTargetsMap
3311 . InstallPlan.toList
3312 $ elaboratedPlan
3314 -- | This is a temporary data type, where we temporarily
3315 -- override the graph dependencies of an 'ElaboratedPackage',
3316 -- so we can take a closure over them. We'll throw out the
3317 -- overridden dependencies when we're done so it's strictly temporary.
3319 -- For 'ElaboratedComponent', this the cached unit IDs always
3320 -- coincide with the real thing.
3321 data PrunedPackage = PrunedPackage ElaboratedConfiguredPackage [UnitId]
3323 instance Package PrunedPackage where
3324 packageId (PrunedPackage elab _) = packageId elab
3326 instance HasUnitId PrunedPackage where
3327 installedUnitId = Graph.nodeKey
3329 instance Graph.IsNode PrunedPackage where
3330 type Key PrunedPackage = UnitId
3331 nodeKey (PrunedPackage elab _) = Graph.nodeKey elab
3332 nodeNeighbors (PrunedPackage _ deps) = deps
3334 fromPrunedPackage :: PrunedPackage -> ElaboratedConfiguredPackage
3335 fromPrunedPackage (PrunedPackage elab _) = elab
3337 -- | Set the build targets based on the user targets (but not rev deps yet).
3338 -- This is required before we can prune anything.
3339 setRootTargets
3340 :: TargetAction
3341 -> Map UnitId [ComponentTarget]
3342 -> [ElaboratedPlanPackage]
3343 -> [ElaboratedPlanPackage]
3344 setRootTargets targetAction perPkgTargetsMap =
3345 assert (not (Map.null perPkgTargetsMap)) $
3346 assert (all (not . null) (Map.elems perPkgTargetsMap)) $
3347 map (mapConfiguredPackage setElabBuildTargets)
3348 where
3349 -- Set the targets we'll build for this package/component. This is just
3350 -- based on the root targets from the user, not targets implied by reverse
3351 -- dependencies. Those comes in the second pass once we know the rev deps.
3353 setElabBuildTargets elab =
3354 case ( Map.lookup (installedUnitId elab) perPkgTargetsMap
3355 , targetAction
3356 ) of
3357 (Nothing, _) -> elab
3358 (Just tgts, TargetActionConfigure) -> elab{elabConfigureTargets = tgts}
3359 (Just tgts, TargetActionBuild) -> elab{elabBuildTargets = tgts}
3360 (Just tgts, TargetActionTest) -> elab{elabTestTargets = tgts}
3361 (Just tgts, TargetActionBench) -> elab{elabBenchTargets = tgts}
3362 (Just tgts, TargetActionRepl) ->
3363 elab
3364 { elabReplTarget = tgts
3365 , elabBuildHaddocks = False
3366 , elabBuildStyle = BuildInplaceOnly InMemory
3368 (Just tgts, TargetActionHaddock) ->
3369 foldr
3370 setElabHaddockTargets
3371 ( elab
3372 { elabHaddockTargets = tgts
3373 , elabBuildHaddocks = True
3376 tgts
3378 setElabHaddockTargets tgt elab
3379 | isTestComponentTarget tgt = elab{elabHaddockTestSuites = True}
3380 | isBenchComponentTarget tgt = elab{elabHaddockBenchmarks = True}
3381 | isForeignLibComponentTarget tgt = elab{elabHaddockForeignLibs = True}
3382 | isExeComponentTarget tgt = elab{elabHaddockExecutables = True}
3383 | isSubLibComponentTarget tgt = elab{elabHaddockInternal = True}
3384 | otherwise = elab
3386 -- | Assuming we have previously set the root build targets (i.e. the user
3387 -- targets but not rev deps yet), the first pruning pass does two things:
3389 -- * A first go at determining which optional stanzas (testsuites, benchmarks)
3390 -- are needed. We have a second go in the next pass.
3391 -- * Take the dependency closure using pruned dependencies. We prune deps that
3392 -- are used only by unneeded optional stanzas. These pruned deps are only
3393 -- used for the dependency closure and are not persisted in this pass.
3394 pruneInstallPlanPass1
3395 :: [ElaboratedPlanPackage]
3396 -> [ElaboratedPlanPackage]
3397 pruneInstallPlanPass1 pkgs
3398 -- if there are repl targets, we need to do a bit more work
3399 -- See Note [Pruning for Multi Repl]
3400 | anyMultiReplTarget = graph_with_repl_targets
3401 -- otherwise we'll do less
3402 | otherwise = pruned_packages
3403 where
3404 pkgs' :: [InstallPlan.GenericPlanPackage IPI.InstalledPackageInfo PrunedPackage]
3405 pkgs' = map (mapConfiguredPackage prune) pkgs
3407 prune :: ElaboratedConfiguredPackage -> PrunedPackage
3408 prune elab = PrunedPackage elab' (pruneOptionalDependencies elab')
3409 where
3410 elab' = addOptionalStanzas elab
3412 graph = Graph.fromDistinctList pkgs'
3414 roots :: [UnitId]
3415 roots = mapMaybe find_root pkgs'
3417 -- Make a closed graph by calculating the closure from the roots
3418 pruned_packages :: [ElaboratedPlanPackage]
3419 pruned_packages = map (mapConfiguredPackage fromPrunedPackage) (fromMaybe [] $ Graph.closure graph roots)
3421 closed_graph :: Graph.Graph ElaboratedPlanPackage
3422 closed_graph = Graph.fromDistinctList pruned_packages
3424 -- whether any package has repl targets enabled, and we need to use multi-repl.
3425 anyMultiReplTarget :: Bool
3426 anyMultiReplTarget = length repls > 1
3427 where
3428 repls = filter is_repl_gpp pkgs'
3429 is_repl_gpp (InstallPlan.Configured pkg) = is_repl_pp pkg
3430 is_repl_gpp _ = False
3432 is_repl_pp (PrunedPackage elab _) = not (null (elabReplTarget elab))
3434 -- Anything which is inplace and left after pruning could be a repl target, then just need to check the
3435 -- reverse closure after calculating roots to capture dependencies which are on the path between roots.
3436 -- In order to start a multi-repl session with all the desired targets we need to load all these components into
3437 -- the repl at once to satisfy the closure property.
3438 all_desired_repl_targets = Set.fromList [elabUnitId cp | InstallPlan.Configured cp <- fromMaybe [] $ Graph.revClosure closed_graph roots]
3440 add_repl_target :: ElaboratedConfiguredPackage -> ElaboratedConfiguredPackage
3441 add_repl_target ecp
3442 | elabUnitId ecp `Set.member` all_desired_repl_targets =
3444 { elabReplTarget = maybeToList (ComponentTarget <$> (elabComponentName ecp) <*> pure WholeComponent)
3445 , elabBuildStyle = BuildInplaceOnly InMemory
3447 | otherwise = ecp
3449 -- Add the repl target information to the ElaboratedPlanPackages
3450 graph_with_repl_targets
3451 | anyMultiReplTarget = map (mapConfiguredPackage add_repl_target) (Graph.toList closed_graph)
3452 | otherwise = Graph.toList closed_graph
3454 is_root :: PrunedPackage -> Maybe UnitId
3455 is_root (PrunedPackage elab _) =
3456 if not $
3458 [ null (elabConfigureTargets elab)
3459 , null (elabBuildTargets elab)
3460 , null (elabTestTargets elab)
3461 , null (elabBenchTargets elab)
3462 , null (elabReplTarget elab)
3463 , null (elabHaddockTargets elab)
3465 then Just (installedUnitId elab)
3466 else Nothing
3468 find_root (InstallPlan.Configured pkg) = is_root pkg
3469 -- When using the extra-packages stanza we need to
3470 -- look at installed packages as well.
3471 find_root (InstallPlan.Installed pkg) = is_root pkg
3472 find_root _ = Nothing
3474 -- Note [Sticky enabled testsuites]
3475 -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
3476 -- The testsuite and benchmark targets are somewhat special in that we need
3477 -- to configure the packages with them enabled, and we need to do that even
3478 -- if we only want to build one of several testsuites.
3480 -- There are two cases in which we will enable the testsuites (or
3481 -- benchmarks): if one of the targets is a testsuite, or if all of the
3482 -- testsuite dependencies are already cached in the store. The rationale
3483 -- for the latter is to minimise how often we have to reconfigure due to
3484 -- the particular targets we choose to build. Otherwise choosing to build
3485 -- a testsuite target, and then later choosing to build an exe target
3486 -- would involve unnecessarily reconfiguring the package with testsuites
3487 -- disabled. Technically this introduces a little bit of stateful
3488 -- behaviour to make this "sticky", but it should be benign.
3490 -- Decide whether or not to enable testsuites and benchmarks.
3491 -- See [Sticky enabled testsuites]
3492 addOptionalStanzas :: ElaboratedConfiguredPackage -> ElaboratedConfiguredPackage
3493 addOptionalStanzas elab@ElaboratedConfiguredPackage{elabPkgOrComp = ElabPackage pkg} =
3494 elab
3495 { elabPkgOrComp = ElabPackage (pkg{pkgStanzasEnabled = stanzas})
3497 where
3498 stanzas :: OptionalStanzaSet
3499 -- By default, we enabled all stanzas requested by the user,
3500 -- as per elabStanzasRequested, done in
3501 -- 'elaborateSolverToPackage'
3502 stanzas =
3503 pkgStanzasEnabled pkg
3504 -- optionalStanzasRequiredByTargets has to be done at
3505 -- prune-time because it depends on 'elabTestTargets'
3506 -- et al, which is done by 'setRootTargets' at the
3507 -- beginning of pruning.
3508 <> optionalStanzasRequiredByTargets elab
3509 -- optionalStanzasWithDepsAvailable has to be done at
3510 -- prune-time because it depends on what packages are
3511 -- installed, which is not known until after improvement
3512 -- (pruning is done after improvement)
3513 <> optionalStanzasWithDepsAvailable availablePkgs elab pkg
3514 addOptionalStanzas elab = elab
3516 -- Calculate package dependencies but cut out those needed only by
3517 -- optional stanzas that we've determined we will not enable.
3518 -- These pruned deps are not persisted in this pass since they're based on
3519 -- the optional stanzas and we'll make further tweaks to the optional
3520 -- stanzas in the next pass.
3522 pruneOptionalDependencies :: ElaboratedConfiguredPackage -> [UnitId]
3523 pruneOptionalDependencies elab@ElaboratedConfiguredPackage{elabPkgOrComp = ElabComponent _} =
3524 InstallPlan.depends elab -- no pruning
3525 pruneOptionalDependencies ElaboratedConfiguredPackage{elabPkgOrComp = ElabPackage pkg} =
3526 (CD.flatDeps . CD.filterDeps keepNeeded) (pkgOrderDependencies pkg)
3527 where
3528 keepNeeded (CD.ComponentTest _) _ = TestStanzas `optStanzaSetMember` stanzas
3529 keepNeeded (CD.ComponentBench _) _ = BenchStanzas `optStanzaSetMember` stanzas
3530 keepNeeded _ _ = True
3531 stanzas = pkgStanzasEnabled pkg
3533 optionalStanzasRequiredByTargets
3534 :: ElaboratedConfiguredPackage
3535 -> OptionalStanzaSet
3536 optionalStanzasRequiredByTargets pkg =
3537 optStanzaSetFromList
3538 [ stanza
3539 | ComponentTarget cname _ <-
3540 elabBuildTargets pkg
3541 ++ elabTestTargets pkg
3542 ++ elabBenchTargets pkg
3543 ++ elabReplTarget pkg
3544 ++ elabHaddockTargets pkg
3545 , stanza <-
3546 maybeToList $
3547 componentOptionalStanza $
3548 CD.componentNameToComponent cname
3551 availablePkgs =
3552 Set.fromList
3553 [ installedUnitId pkg
3554 | InstallPlan.PreExisting pkg <- pkgs
3558 Note [Pruning for Multi Repl]
3559 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
3561 For a multi-repl session, where we load more than one component into a GHCi repl,
3562 it is required to uphold the so-called *closure property*.
3563 This property, whose exact Note you can read in the GHC codebase, states
3564 roughly:
3566 \* If a component you want to load into a repl session transitively depends on a
3567 component which transitively depends on another component you want to
3568 load into the repl, then this component needs to be loaded
3569 into the repl session as well.
3571 We make sure here, that this property is upheld, by calculating the
3572 graph of components that we need to load into the repl given the set of 'roots' which
3573 are the targets specified by the user.
3575 Practically, this is simply achieved by traversing all dependencies of
3576 our roots (graph closure), and then from this closed graph, we calculate
3577 the reverse closure, which gives us all components that depend on
3578 'roots'. Thus, the result is a list of components that we need to load
3579 into the repl to uphold the closure property.
3582 -- | Given a set of already installed packages @availablePkgs@,
3583 -- determine the set of available optional stanzas from @pkg@
3584 -- which have all of their dependencies already installed. This is used
3585 -- to implement "sticky" testsuites, where once we have installed
3586 -- all of the deps needed for the test suite, we go ahead and
3587 -- enable it always.
3588 optionalStanzasWithDepsAvailable
3589 :: Set UnitId
3590 -> ElaboratedConfiguredPackage
3591 -> ElaboratedPackage
3592 -> OptionalStanzaSet
3593 optionalStanzasWithDepsAvailable availablePkgs elab pkg =
3594 optStanzaSetFromList
3595 [ stanza
3596 | stanza <- optStanzaSetToList (elabStanzasAvailable elab)
3597 , let deps :: [UnitId]
3598 deps =
3599 CD.select
3600 (optionalStanzaDeps stanza)
3601 -- TODO: probably need to select other
3602 -- dep types too eventually
3603 (pkgOrderDependencies pkg)
3604 , all (`Set.member` availablePkgs) deps
3606 where
3607 optionalStanzaDeps TestStanzas (CD.ComponentTest _) = True
3608 optionalStanzaDeps BenchStanzas (CD.ComponentBench _) = True
3609 optionalStanzaDeps _ _ = False
3611 -- The second pass does three things:
3614 -- * A second go at deciding which optional stanzas to enable.
3616 -- * Prune the dependencies based on the final choice of optional stanzas.
3618 -- * Extend the targets within each package to build, now we know the reverse
3620 -- dependencies, ie we know which libs are needed as deps by other packages.
3622 -- Achieving sticky behaviour with enabling\/disabling optional stanzas is
3623 -- tricky. The first approximation was handled by the first pass above, but
3624 -- it's not quite enough. That pass will enable stanzas if all of the deps
3625 -- of the optional stanza are already installed /in the store/. That's important
3626 -- but it does not account for dependencies that get built inplace as part of
3627 -- the project. We cannot take those inplace build deps into account in the
3628 -- pruning pass however because we don't yet know which ones we're going to
3629 -- build. Once we do know, we can have another go and enable stanzas that have
3630 -- all their deps available. Now we can consider all packages in the pruned
3631 -- plan to be available, including ones we already decided to build from
3632 -- source.
3634 -- Deciding which targets to build depends on knowing which packages have
3635 -- reverse dependencies (ie are needed). This requires the result of first
3636 -- pass, which is another reason we have to split it into two passes.
3638 -- Note that just because we might enable testsuites or benchmarks (in the
3639 -- first or second pass) doesn't mean that we build all (or even any) of them.
3640 -- That depends on which targets we picked in the first pass.
3642 pruneInstallPlanPass2
3643 :: [ElaboratedPlanPackage]
3644 -> [ElaboratedPlanPackage]
3645 pruneInstallPlanPass2 pkgs =
3646 map (mapConfiguredPackage setStanzasDepsAndTargets) pkgs
3647 where
3648 setStanzasDepsAndTargets elab =
3649 elab
3650 { elabBuildTargets =
3651 ordNub $
3652 elabBuildTargets elab
3653 ++ libTargetsRequiredForRevDeps
3654 ++ exeTargetsRequiredForRevDeps
3655 , elabPkgOrComp =
3656 case elabPkgOrComp elab of
3657 ElabPackage pkg ->
3658 let stanzas =
3659 pkgStanzasEnabled pkg
3660 <> optionalStanzasWithDepsAvailable availablePkgs elab pkg
3662 keepNeeded :: CD.Component -> a -> Bool
3663 keepNeeded (CD.ComponentTest _) _ = TestStanzas `optStanzaSetMember` stanzas
3664 keepNeeded (CD.ComponentBench _) _ = BenchStanzas `optStanzaSetMember` stanzas
3665 keepNeeded _ _ = True
3666 in ElabPackage $
3668 { pkgStanzasEnabled =
3669 stanzas
3670 , pkgLibDependencies =
3671 CD.mapDeps (\_ -> map addInternal) $
3672 CD.filterDeps keepNeeded (pkgLibDependencies pkg)
3673 , pkgExeDependencies =
3674 CD.filterDeps keepNeeded (pkgExeDependencies pkg)
3675 , pkgExeDependencyPaths =
3676 CD.filterDeps keepNeeded (pkgExeDependencyPaths pkg)
3678 ElabComponent comp ->
3679 ElabComponent $
3680 comp
3681 { compLibDependencies = map addInternal (compLibDependencies comp)
3684 where
3685 -- We initially assume that all the dependencies are external (hence the boolean is always
3686 -- False) and here we correct the dependencies so the right packages are marked promised.
3687 addInternal (cid, _) = (cid, (cid `Set.member` inMemoryTargets))
3689 libTargetsRequiredForRevDeps =
3691 | installedUnitId elab `Set.member` hasReverseLibDeps
3692 , let c = ComponentTarget (CLibName Cabal.defaultLibName) WholeComponent
3693 , -- Don't enable building for anything which is being build in memory
3694 elabBuildStyle elab /= BuildInplaceOnly InMemory
3696 exeTargetsRequiredForRevDeps =
3697 -- TODO: allow requesting executable with different name
3698 -- than package name
3699 [ ComponentTarget
3700 ( Cabal.CExeName $
3701 packageNameToUnqualComponentName $
3702 packageName $
3703 elabPkgSourceId elab
3705 WholeComponent
3706 | installedUnitId elab `Set.member` hasReverseExeDeps
3709 availablePkgs :: Set UnitId
3710 availablePkgs = Set.fromList (map installedUnitId pkgs)
3712 inMemoryTargets :: Set ConfiguredId
3713 inMemoryTargets = do
3714 Set.fromList
3715 [ configuredId pkg
3716 | InstallPlan.Configured pkg <- pkgs
3717 , BuildInplaceOnly InMemory <- [elabBuildStyle pkg]
3720 hasReverseLibDeps :: Set UnitId
3721 hasReverseLibDeps =
3722 Set.fromList
3723 [ depid
3724 | InstallPlan.Configured pkg <- pkgs
3725 , depid <- elabOrderLibDependencies pkg
3728 hasReverseExeDeps :: Set UnitId
3729 hasReverseExeDeps =
3730 Set.fromList
3731 [ depid
3732 | InstallPlan.Configured pkg <- pkgs
3733 , depid <- elabOrderExeDependencies pkg
3736 mapConfiguredPackage
3737 :: (srcpkg -> srcpkg')
3738 -> InstallPlan.GenericPlanPackage ipkg srcpkg
3739 -> InstallPlan.GenericPlanPackage ipkg srcpkg'
3740 mapConfiguredPackage f (InstallPlan.Configured pkg) =
3741 InstallPlan.Configured (f pkg)
3742 mapConfiguredPackage f (InstallPlan.Installed pkg) =
3743 InstallPlan.Installed (f pkg)
3744 mapConfiguredPackage _ (InstallPlan.PreExisting pkg) =
3745 InstallPlan.PreExisting pkg
3747 ------------------------------------
3748 -- Support for --only-dependencies
3751 -- | Try to remove the given targets from the install plan.
3753 -- This is not always possible.
3754 pruneInstallPlanToDependencies
3755 :: Set UnitId
3756 -> ElaboratedInstallPlan
3757 -> Either
3758 CannotPruneDependencies
3759 ElaboratedInstallPlan
3760 pruneInstallPlanToDependencies pkgTargets installPlan =
3761 assert
3762 ( all
3763 (isJust . InstallPlan.lookup installPlan)
3764 (Set.toList pkgTargets)
3766 $ fmap (InstallPlan.new (InstallPlan.planIndepGoals installPlan))
3767 . checkBrokenDeps
3768 . Graph.fromDistinctList
3769 . filter (\pkg -> installedUnitId pkg `Set.notMember` pkgTargets)
3770 . InstallPlan.toList
3771 $ installPlan
3772 where
3773 -- Our strategy is to remove the packages we don't want and then check
3774 -- if the remaining graph is broken or not, ie any packages with dangling
3775 -- dependencies. If there are then we cannot prune the given targets.
3776 checkBrokenDeps
3777 :: Graph.Graph ElaboratedPlanPackage
3778 -> Either
3779 CannotPruneDependencies
3780 (Graph.Graph ElaboratedPlanPackage)
3781 checkBrokenDeps graph =
3782 case Graph.broken graph of
3783 [] -> Right graph
3784 brokenPackages ->
3785 Left $
3786 CannotPruneDependencies
3787 [ (pkg, missingDeps)
3788 | (pkg, missingDepIds) <- brokenPackages
3789 , let missingDeps = mapMaybe lookupDep missingDepIds
3791 where
3792 -- lookup in the original unpruned graph
3793 lookupDep = InstallPlan.lookup installPlan
3795 -- | It is not always possible to prune to only the dependencies of a set of
3796 -- targets. It may be the case that removing a package leaves something else
3797 -- that still needed the pruned package.
3799 -- This lists all the packages that would be broken, and their dependencies
3800 -- that would be missing if we did prune.
3801 newtype CannotPruneDependencies
3802 = CannotPruneDependencies
3803 [ ( ElaboratedPlanPackage
3804 , [ElaboratedPlanPackage]
3807 deriving (Show)
3809 -- The other aspects of our Setup.hs policy lives here where we decide on
3810 -- the 'SetupScriptOptions'.
3812 -- Our current policy for the 'SetupCustomImplicitDeps' case is that we
3813 -- try to make the implicit deps cover everything, and we don't allow the
3814 -- compiler to pick up other deps. This may or may not be sustainable, and
3815 -- we might have to allow the deps to be non-exclusive, but that itself would
3816 -- be tricky since we would have to allow the Setup access to all the packages
3817 -- in the store and local dbs.
3819 setupHsScriptOptions
3820 :: ElaboratedReadyPackage
3821 -> ElaboratedInstallPlan
3822 -> ElaboratedSharedConfig
3823 -> DistDirLayout
3824 -> SymbolicPath CWD (Dir Pkg)
3825 -> SymbolicPath Pkg (Dir Dist)
3826 -> Bool
3827 -> Lock
3828 -> SetupScriptOptions
3829 -- TODO: Fix this so custom is a separate component. Custom can ALWAYS
3830 -- be a separate component!!!
3831 setupHsScriptOptions
3832 (ReadyPackage elab@ElaboratedConfiguredPackage{..})
3833 plan
3834 ElaboratedSharedConfig{..}
3835 distdir
3836 srcdir
3837 builddir
3838 isParallelBuild
3839 cacheLock =
3840 SetupScriptOptions
3841 { useCabalVersion = thisVersion elabSetupScriptCliVersion
3842 , useCabalSpecVersion =
3843 if PD.buildType elabPkgDescription == PD.Hooks
3844 then -- NB: we don't want to commit to a Cabal version here:
3845 -- - all that should matter for Hooks build-type is the
3846 -- version of Cabal-hooks, not of Cabal,
3847 -- - if we commit to a Cabal version, the logic in
3848 Nothing
3849 else Just elabSetupScriptCliVersion
3850 , useCompiler = Just pkgConfigCompiler
3851 , usePlatform = Just pkgConfigPlatform
3852 , usePackageDB = elabSetupPackageDBStack
3853 , usePackageIndex = Nothing
3854 , useDependencies =
3855 [ (uid, srcid)
3856 | (ConfiguredId srcid (Just (CLibName LMainLibName)) uid, _) <-
3857 elabSetupDependencies elab
3859 , useDependenciesExclusive = True
3860 , useVersionMacros = elabSetupScriptStyle == SetupCustomExplicitDeps
3861 , useProgramDb = pkgConfigCompilerProgs
3862 , useDistPref = builddir
3863 , useLoggingHandle = Nothing -- this gets set later
3864 , useWorkingDir = Just srcdir
3865 , useExtraPathEnv = elabExeDependencyPaths elab ++ elabProgramPathExtra
3866 , -- note that the above adds the extra-prog-path directly following the elaborated
3867 -- dep paths, so that it overrides the normal path, but _not_ the elaborated extensions
3868 -- for build-tools-depends.
3869 useExtraEnvOverrides = dataDirsEnvironmentForPlan distdir plan
3870 , useWin32CleanHack = False -- TODO: [required eventually]
3871 , forceExternalSetupMethod = isParallelBuild
3872 , setupCacheLock = Just cacheLock
3873 , isInteractive = False
3876 -- | To be used for the input for elaborateInstallPlan.
3878 -- TODO: [code cleanup] make InstallDirs.defaultInstallDirs pure.
3879 userInstallDirTemplates
3880 :: Compiler
3881 -> IO InstallDirs.InstallDirTemplates
3882 userInstallDirTemplates compiler = do
3883 InstallDirs.defaultInstallDirs
3884 (compilerFlavor compiler)
3885 True -- user install
3886 False -- unused
3888 storePackageInstallDirs
3889 :: StoreDirLayout
3890 -> Compiler
3891 -> InstalledPackageId
3892 -> InstallDirs.InstallDirs FilePath
3893 storePackageInstallDirs storeDirLayout compiler ipkgid =
3894 storePackageInstallDirs' storeDirLayout compiler $ newSimpleUnitId ipkgid
3896 storePackageInstallDirs'
3897 :: StoreDirLayout
3898 -> Compiler
3899 -> UnitId
3900 -> InstallDirs.InstallDirs FilePath
3901 storePackageInstallDirs'
3902 StoreDirLayout
3903 { storePackageDirectory
3904 , storeDirectory
3906 compiler
3907 unitid =
3908 InstallDirs.InstallDirs{..}
3909 where
3910 store = storeDirectory compiler
3911 prefix = storePackageDirectory compiler unitid
3912 bindir = prefix </> "bin"
3913 libdir = prefix </> "lib"
3914 libsubdir = ""
3915 -- Note: on macOS, we place libraries into
3916 -- @store/lib@ to work around the load
3917 -- command size limit of macOSs mach-o linker.
3918 -- See also @PackageHash.hashedInstalledPackageIdVeryShort@
3919 dynlibdir
3920 | buildOS == OSX = store </> "lib"
3921 | otherwise = libdir
3922 flibdir = libdir
3923 libexecdir = prefix </> "libexec"
3924 libexecsubdir = ""
3925 includedir = libdir </> "include"
3926 datadir = prefix </> "share"
3927 datasubdir = ""
3928 docdir = datadir </> "doc"
3929 mandir = datadir </> "man"
3930 htmldir = docdir </> "html"
3931 haddockdir = htmldir
3932 sysconfdir = prefix </> "etc"
3934 computeInstallDirs
3935 :: StoreDirLayout
3936 -> InstallDirs.InstallDirTemplates
3937 -> ElaboratedSharedConfig
3938 -> ElaboratedConfiguredPackage
3939 -> InstallDirs.InstallDirs FilePath
3940 computeInstallDirs storeDirLayout defaultInstallDirs elaboratedShared elab
3941 | isInplaceBuildStyle (elabBuildStyle elab) =
3942 -- use the ordinary default install dirs
3943 ( InstallDirs.absoluteInstallDirs
3944 (elabPkgSourceId elab)
3945 (elabUnitId elab)
3946 (compilerInfo (pkgConfigCompiler elaboratedShared))
3947 InstallDirs.NoCopyDest
3948 (pkgConfigPlatform elaboratedShared)
3949 defaultInstallDirs
3951 { -- absoluteInstallDirs sets these as 'undefined' but we have
3952 -- to use them as "Setup.hs configure" args
3953 InstallDirs.libsubdir = ""
3954 , InstallDirs.libexecsubdir = ""
3955 , InstallDirs.datasubdir = ""
3957 | otherwise =
3958 -- use special simplified install dirs
3959 storePackageInstallDirs'
3960 storeDirLayout
3961 (pkgConfigCompiler elaboratedShared)
3962 (elabUnitId elab)
3964 -- TODO: [code cleanup] perhaps reorder this code
3965 -- based on the ElaboratedInstallPlan + ElaboratedSharedConfig,
3966 -- make the various Setup.hs {configure,build,copy} flags
3967 setupHsConfigureFlags
3968 :: Monad m
3969 => (FilePath -> m (SymbolicPath Pkg (Dir PkgDB)))
3970 -- ^ How to transform a path which is relative to cabal-install cwd to one which
3971 -- is relative to the route of the package about to be compiled. The simplest way
3972 -- to do this is to convert the potentially relative path into an absolute path.
3973 -> ElaboratedInstallPlan
3974 -> ElaboratedReadyPackage
3975 -> ElaboratedSharedConfig
3976 -> Cabal.CommonSetupFlags
3977 -> m Cabal.ConfigFlags
3978 setupHsConfigureFlags
3979 mkSymbolicPath
3980 plan
3981 (ReadyPackage elab@ElaboratedConfiguredPackage{..})
3982 sharedConfig@ElaboratedSharedConfig{..}
3983 configCommonFlags = do
3984 -- explicitly clear, then our package db stack
3985 -- TODO: [required eventually] have to do this differently for older Cabal versions
3986 configPackageDBs <- (traverse . traverse . traverse) mkSymbolicPath (Nothing : map Just elabBuildPackageDBStack)
3987 return $
3988 sanityCheckElaboratedConfiguredPackage
3989 sharedConfig
3990 elab
3991 Cabal.ConfigFlags{..}
3992 where
3993 Cabal.ConfigFlags
3994 { configVanillaLib
3995 , configSharedLib
3996 , configStaticLib
3997 , configDynExe
3998 , configFullyStaticExe
3999 , configGHCiLib
4000 , -- , configProfExe -- overridden
4001 configProfLib
4002 , configProfShared
4003 , -- , configProf -- overridden
4004 configProfDetail
4005 , configProfLibDetail
4006 , configCoverage
4007 , configLibCoverage
4008 , configRelocatable
4009 , configOptimization
4010 , configSplitSections
4011 , configSplitObjs
4012 , configStripExes
4013 , configStripLibs
4014 , configDebugInfo
4015 } = LBC.buildOptionsConfigFlags elabBuildOptions
4016 configProfExe = mempty
4017 configProf = toFlag $ LBC.withProfExe elabBuildOptions
4019 configInstantiateWith = Map.toList elabInstantiatedWith
4021 configDeterministic = mempty -- doesn't matter, configIPID/configCID overridese
4022 configIPID = case elabPkgOrComp of
4023 ElabPackage pkg -> toFlag (prettyShow (pkgInstalledId pkg))
4024 ElabComponent _ -> mempty
4025 configCID = case elabPkgOrComp of
4026 ElabPackage _ -> mempty
4027 ElabComponent _ -> toFlag elabComponentId
4029 configProgramPaths = Map.toList elabProgramPaths
4030 configProgramArgs
4031 | {- elabSetupScriptCliVersion < mkVersion [1,24,3] -} True =
4032 -- workaround for <https://github.com/haskell/cabal/issues/4010>
4034 -- It turns out, that even with Cabal 2.0, there's still cases such as e.g.
4035 -- custom Setup.hs scripts calling out to GHC even when going via
4036 -- @runProgram ghcProgram@, as e.g. happy does in its
4037 -- <http://hackage.haskell.org/package/happy-1.19.5/src/Setup.lhs>
4038 -- (see also <https://github.com/haskell/cabal/pull/4433#issuecomment-299396099>)
4040 -- So for now, let's pass the rather harmless and idempotent
4041 -- `-hide-all-packages` flag to all invocations (which has
4042 -- the benefit that every GHC invocation starts with a
4043 -- consistently well-defined clean slate) until we find a
4044 -- better way.
4045 Map.toList $
4046 Map.insertWith
4047 (++)
4048 "ghc"
4049 ["-hide-all-packages"]
4050 elabProgramArgs
4051 configProgramPathExtra = toNubList elabProgramPathExtra
4052 configHcFlavor = toFlag (compilerFlavor pkgConfigCompiler)
4053 configHcPath = mempty -- we use configProgramPaths instead
4054 configHcPkg = mempty -- we use configProgramPaths instead
4055 configDumpBuildInfo = toFlag elabDumpBuildInfo
4057 configConfigurationsFlags = elabFlagAssignment
4058 configConfigureArgs = elabConfigureScriptArgs
4059 configExtraLibDirs = fmap makeSymbolicPath $ elabExtraLibDirs
4060 configExtraLibDirsStatic = fmap makeSymbolicPath $ elabExtraLibDirsStatic
4061 configExtraFrameworkDirs = fmap makeSymbolicPath $ elabExtraFrameworkDirs
4062 configExtraIncludeDirs = fmap makeSymbolicPath $ elabExtraIncludeDirs
4063 configProgPrefix = maybe mempty toFlag elabProgPrefix
4064 configProgSuffix = maybe mempty toFlag elabProgSuffix
4066 configInstallDirs =
4067 fmap
4068 (toFlag . InstallDirs.toPathTemplate)
4069 elabInstallDirs
4071 -- we only use configDependencies, unless we're talking to an old Cabal
4072 -- in which case we use configConstraints
4073 -- NB: This does NOT use InstallPlan.depends, which includes executable
4074 -- dependencies which should NOT be fed in here (also you don't have
4075 -- enough info anyway)
4077 configDependencies =
4078 [ cidToGivenComponent cid
4079 | (cid, is_internal) <- elabLibDependencies elab
4080 , not is_internal
4083 configPromisedDependencies =
4084 [ cidToPromisedComponent cid
4085 | (cid, is_internal) <- elabLibDependencies elab
4086 , is_internal
4089 configConstraints =
4090 case elabPkgOrComp of
4091 ElabPackage _ ->
4092 [ thisPackageVersionConstraint srcid
4093 | (ConfiguredId srcid _ _uid, _) <- elabLibDependencies elab
4095 ElabComponent _ -> []
4097 configTests = case elabPkgOrComp of
4098 ElabPackage pkg -> toFlag (TestStanzas `optStanzaSetMember` pkgStanzasEnabled pkg)
4099 ElabComponent _ -> mempty
4100 configBenchmarks = case elabPkgOrComp of
4101 ElabPackage pkg -> toFlag (BenchStanzas `optStanzaSetMember` pkgStanzasEnabled pkg)
4102 ElabComponent _ -> mempty
4104 configExactConfiguration = toFlag True
4105 configFlagError = mempty -- TODO: [research required] appears not to be implemented
4106 configScratchDir = mempty -- never use
4107 configUserInstall = mempty -- don't rely on defaults
4108 configPrograms_ = mempty -- never use, shouldn't exist
4109 configUseResponseFiles = mempty
4110 configAllowDependingOnPrivateLibs = Flag $ not $ libraryVisibilitySupported pkgConfigCompiler
4111 configIgnoreBuildTools = mempty
4113 cidToGivenComponent :: ConfiguredId -> GivenComponent
4114 cidToGivenComponent (ConfiguredId srcid mb_cn cid) = GivenComponent (packageName srcid) ln cid
4115 where
4116 ln = case mb_cn of
4117 Just (CLibName lname) -> lname
4118 Just _ -> error "non-library dependency"
4119 Nothing -> LMainLibName
4121 configCoverageFor = determineCoverageFor elab plan
4123 cidToPromisedComponent :: ConfiguredId -> PromisedComponent
4124 cidToPromisedComponent (ConfiguredId srcid mb_cn cid) =
4125 PromisedComponent srcid ln cid
4126 where
4127 ln = case mb_cn of
4128 Just (CLibName lname) -> lname
4129 Just _ -> error "non-library dependency"
4130 Nothing -> LMainLibName
4132 setupHsConfigureArgs
4133 :: ElaboratedConfiguredPackage
4134 -> [String]
4135 setupHsConfigureArgs (ElaboratedConfiguredPackage{elabPkgOrComp = ElabPackage _}) = []
4136 setupHsConfigureArgs elab@(ElaboratedConfiguredPackage{elabPkgOrComp = ElabComponent comp}) =
4137 [showComponentTarget (packageId elab) (ComponentTarget cname WholeComponent)]
4138 where
4139 cname =
4140 fromMaybe
4141 (error "setupHsConfigureArgs: trying to configure setup")
4142 (compComponentName comp)
4144 setupHsCommonFlags
4145 :: Verbosity
4146 -> Maybe (SymbolicPath CWD (Dir Pkg))
4147 -> SymbolicPath Pkg (Dir Dist)
4148 -> Bool
4149 -> Cabal.CommonSetupFlags
4150 setupHsCommonFlags verbosity mbWorkDir builddir keepTempFiles =
4151 Cabal.CommonSetupFlags
4152 { setupDistPref = toFlag builddir
4153 , setupVerbosity = toFlag verbosity
4154 , setupCabalFilePath = mempty
4155 , setupWorkingDir = maybeToFlag mbWorkDir
4156 , setupTargets = []
4157 , setupKeepTempFiles = toFlag keepTempFiles
4160 setupHsBuildFlags
4161 :: Flag String
4162 -> ElaboratedConfiguredPackage
4163 -> ElaboratedSharedConfig
4164 -> Cabal.CommonSetupFlags
4165 -> Cabal.BuildFlags
4166 setupHsBuildFlags par_strat elab _ common =
4167 Cabal.BuildFlags
4168 { buildCommonFlags = common
4169 , buildProgramPaths = mempty -- unused, set at configure time
4170 , buildProgramArgs = mempty -- unused, set at configure time
4171 , buildNumJobs = mempty -- TODO: [nice to have] sometimes want to use toFlag (Just numBuildJobs),
4172 , buildUseSemaphore =
4173 if elabSetupScriptCliVersion elab >= mkVersion [3, 11, 0, 0]
4174 then -- Cabal 3.11 is the first version that supports parallelism semaphores
4175 par_strat
4176 else mempty
4179 setupHsBuildArgs :: ElaboratedConfiguredPackage -> [String]
4180 setupHsBuildArgs elab@(ElaboratedConfiguredPackage{elabPkgOrComp = ElabPackage _})
4181 -- Fix for #3335, don't pass build arguments if it's not supported
4182 | elabSetupScriptCliVersion elab >= mkVersion [1, 17] =
4183 map (showComponentTarget (packageId elab)) (elabBuildTargets elab)
4184 | otherwise =
4186 setupHsBuildArgs (ElaboratedConfiguredPackage{elabPkgOrComp = ElabComponent _}) =
4189 setupHsTestFlags
4190 :: ElaboratedConfiguredPackage
4191 -> Cabal.CommonSetupFlags
4192 -> Cabal.TestFlags
4193 setupHsTestFlags (ElaboratedConfiguredPackage{..}) common =
4194 Cabal.TestFlags
4195 { testCommonFlags = common
4196 , testMachineLog = maybe mempty toFlag elabTestMachineLog
4197 , testHumanLog = maybe mempty toFlag elabTestHumanLog
4198 , testShowDetails = maybe (Flag Cabal.Always) toFlag elabTestShowDetails
4199 , testKeepTix = toFlag elabTestKeepTix
4200 , testWrapper = maybe mempty toFlag elabTestWrapper
4201 , testFailWhenNoTestSuites = toFlag elabTestFailWhenNoTestSuites
4202 , testOptions = elabTestTestOptions
4205 setupHsTestArgs :: ElaboratedConfiguredPackage -> [String]
4206 -- TODO: Does the issue #3335 affects test as well
4207 setupHsTestArgs elab =
4208 mapMaybe (showTestComponentTarget (packageId elab)) (elabTestTargets elab)
4210 setupHsBenchFlags
4211 :: ElaboratedConfiguredPackage
4212 -> ElaboratedSharedConfig
4213 -> Cabal.CommonSetupFlags
4214 -> Cabal.BenchmarkFlags
4215 setupHsBenchFlags (ElaboratedConfiguredPackage{..}) _ common =
4216 Cabal.BenchmarkFlags
4217 { benchmarkCommonFlags = common
4218 , benchmarkOptions = elabBenchmarkOptions
4221 setupHsBenchArgs :: ElaboratedConfiguredPackage -> [String]
4222 setupHsBenchArgs elab =
4223 mapMaybe (showBenchComponentTarget (packageId elab)) (elabBenchTargets elab)
4225 setupHsReplFlags
4226 :: ElaboratedConfiguredPackage
4227 -> ElaboratedSharedConfig
4228 -> Cabal.CommonSetupFlags
4229 -> Cabal.ReplFlags
4230 setupHsReplFlags _ sharedConfig common =
4231 Cabal.ReplFlags
4232 { replCommonFlags = common
4233 , replProgramPaths = mempty -- unused, set at configure time
4234 , replProgramArgs = mempty -- unused, set at configure time
4235 , replReload = mempty -- only used as callback from repl
4236 , replReplOptions = pkgConfigReplOptions sharedConfig -- runtime override for repl flags
4239 setupHsReplArgs :: ElaboratedConfiguredPackage -> [String]
4240 setupHsReplArgs elab =
4241 map (\t -> showComponentTarget (packageId elab) t) (elabReplTarget elab)
4243 setupHsCopyFlags
4244 :: ElaboratedConfiguredPackage
4245 -> ElaboratedSharedConfig
4246 -> Cabal.CommonSetupFlags
4247 -> FilePath
4248 -> Cabal.CopyFlags
4249 setupHsCopyFlags _ _ common destdir =
4250 Cabal.CopyFlags
4251 { copyCommonFlags = common
4252 , copyDest = toFlag (InstallDirs.CopyTo destdir)
4255 setupHsRegisterFlags
4256 :: ElaboratedConfiguredPackage
4257 -> ElaboratedSharedConfig
4258 -> Cabal.CommonSetupFlags
4259 -> FilePath
4260 -> Cabal.RegisterFlags
4261 setupHsRegisterFlags
4262 ElaboratedConfiguredPackage{..}
4264 common
4265 pkgConfFile =
4266 Cabal.RegisterFlags
4267 { registerCommonFlags = common
4268 , regPackageDB = mempty -- misfeature
4269 , regGenScript = mempty -- never use
4270 , regGenPkgConf = toFlag (Just (makeSymbolicPath pkgConfFile))
4271 , regInPlace = case elabBuildStyle of
4272 BuildInplaceOnly{} -> toFlag True
4273 BuildAndInstall -> toFlag False
4274 , regPrintId = mempty -- never use
4277 setupHsHaddockFlags
4278 :: ElaboratedConfiguredPackage
4279 -> ElaboratedSharedConfig
4280 -> BuildTimeSettings
4281 -> Cabal.CommonSetupFlags
4282 -> Cabal.HaddockFlags
4283 setupHsHaddockFlags
4284 (ElaboratedConfiguredPackage{..})
4285 (ElaboratedSharedConfig{..})
4286 _buildTimeSettings
4287 common =
4288 Cabal.HaddockFlags
4289 { haddockCommonFlags = common
4290 , haddockProgramPaths =
4291 case lookupProgram haddockProgram pkgConfigCompilerProgs of
4292 Nothing -> mempty
4293 Just prg ->
4295 ( programName haddockProgram
4296 , locationPath (programLocation prg)
4299 , haddockProgramArgs = mempty -- unused, set at configure time
4300 , haddockHoogle = toFlag elabHaddockHoogle
4301 , haddockHtml = toFlag elabHaddockHtml
4302 , haddockHtmlLocation = maybe mempty toFlag elabHaddockHtmlLocation
4303 , haddockForHackage = toFlag elabHaddockForHackage
4304 , haddockForeignLibs = toFlag elabHaddockForeignLibs
4305 , haddockExecutables = toFlag elabHaddockExecutables
4306 , haddockTestSuites = toFlag elabHaddockTestSuites
4307 , haddockBenchmarks = toFlag elabHaddockBenchmarks
4308 , haddockInternal = toFlag elabHaddockInternal
4309 , haddockCss = maybe mempty toFlag elabHaddockCss
4310 , haddockLinkedSource = toFlag elabHaddockLinkedSource
4311 , haddockQuickJump = toFlag elabHaddockQuickJump
4312 , haddockHscolourCss = maybe mempty toFlag elabHaddockHscolourCss
4313 , haddockContents = maybe mempty toFlag elabHaddockContents
4314 , haddockIndex = maybe mempty toFlag elabHaddockIndex
4315 , haddockBaseUrl = maybe mempty toFlag elabHaddockBaseUrl
4316 , haddockResourcesDir = maybe mempty toFlag elabHaddockResourcesDir
4317 , haddockOutputDir = maybe mempty toFlag elabHaddockOutputDir
4318 , haddockUseUnicode = toFlag elabHaddockUseUnicode
4321 setupHsHaddockArgs :: ElaboratedConfiguredPackage -> [String]
4322 -- TODO: Does the issue #3335 affects test as well
4323 setupHsHaddockArgs elab =
4324 map (showComponentTarget (packageId elab)) (elabHaddockTargets elab)
4326 ------------------------------------------------------------------------------
4328 -- * Sharing installed packages
4330 ------------------------------------------------------------------------------
4333 -- Nix style store management for tarball packages
4335 -- So here's our strategy:
4337 -- We use a per-user nix-style hashed store, but /only/ for tarball packages.
4338 -- So that includes packages from hackage repos (and other http and local
4339 -- tarballs). For packages in local directories we do not register them into
4340 -- the shared store by default, we just build them locally inplace.
4342 -- The reason we do it like this is that it's easy to make stable hashes for
4343 -- tarball packages, and these packages benefit most from sharing. By contrast
4344 -- unpacked dir packages are harder to hash and they tend to change more
4345 -- frequently so there's less benefit to sharing them.
4347 -- When using the nix store approach we have to run the solver *without*
4348 -- looking at the packages installed in the store, just at the source packages
4349 -- (plus core\/global installed packages). Then we do a post-processing pass
4350 -- to replace configured packages in the plan with pre-existing ones, where
4351 -- possible. Where possible of course means where the nix-style package hash
4352 -- equals one that's already in the store.
4354 -- One extra wrinkle is that unless we know package tarball hashes upfront, we
4355 -- will have to download the tarballs to find their hashes. So we have two
4356 -- options: delay replacing source with pre-existing installed packages until
4357 -- the point during the execution of the install plan where we have the
4358 -- tarball, or try to do as much up-front as possible and then check again
4359 -- during plan execution. The former isn't great because we would end up
4360 -- telling users we're going to re-install loads of packages when in fact we
4361 -- would just share them. It'd be better to give as accurate a prediction as
4362 -- we can. The latter is better for users, but we do still have to check
4363 -- during plan execution because it's important that we don't replace existing
4364 -- installed packages even if they have the same package hash, because we
4365 -- don't guarantee ABI stability.
4367 -- TODO: [required eventually] for safety of concurrent installs, we must make sure we register but
4368 -- not replace installed packages with ghc-pkg.
4370 packageHashInputs
4371 :: ElaboratedSharedConfig
4372 -> ElaboratedConfiguredPackage
4373 -> PackageHashInputs
4374 packageHashInputs
4375 pkgshared
4376 elab@( ElaboratedConfiguredPackage
4377 { elabPkgSourceHash = Just srchash
4380 PackageHashInputs
4381 { pkgHashPkgId = packageId elab
4382 , pkgHashComponent =
4383 case elabPkgOrComp elab of
4384 ElabPackage _ -> Nothing
4385 ElabComponent comp -> Just (compSolverName comp)
4386 , pkgHashSourceHash = srchash
4387 , pkgHashPkgConfigDeps = Set.fromList (elabPkgConfigDependencies elab)
4388 , pkgHashDirectDeps =
4389 case elabPkgOrComp elab of
4390 ElabPackage (ElaboratedPackage{..}) ->
4391 Set.fromList $
4392 [ confInstId dep
4393 | (dep, _) <- CD.select relevantDeps pkgLibDependencies
4395 ++ [ confInstId dep
4396 | dep <- CD.select relevantDeps pkgExeDependencies
4398 ElabComponent comp ->
4399 Set.fromList
4400 ( map
4401 confInstId
4402 ( map fst (compLibDependencies comp)
4403 ++ compExeDependencies comp
4406 , pkgHashOtherConfig = packageHashConfigInputs pkgshared elab
4408 where
4409 -- Obviously the main deps are relevant
4410 relevantDeps CD.ComponentLib = True
4411 relevantDeps (CD.ComponentSubLib _) = True
4412 relevantDeps (CD.ComponentFLib _) = True
4413 relevantDeps (CD.ComponentExe _) = True
4414 -- Setup deps can affect the Setup.hs behaviour and thus what is built
4415 relevantDeps CD.ComponentSetup = True
4416 -- However testsuites and benchmarks do not get installed and should not
4417 -- affect the result, so we do not include them.
4418 relevantDeps (CD.ComponentTest _) = False
4419 relevantDeps (CD.ComponentBench _) = False
4420 packageHashInputs _ pkg =
4421 error $
4422 "packageHashInputs: only for packages with source hashes. "
4423 ++ prettyShow (packageId pkg)
4425 packageHashConfigInputs
4426 :: ElaboratedSharedConfig
4427 -> ElaboratedConfiguredPackage
4428 -> PackageHashConfigInputs
4429 packageHashConfigInputs shared@ElaboratedSharedConfig{..} pkg =
4430 PackageHashConfigInputs
4431 { pkgHashCompilerId = compilerId pkgConfigCompiler
4432 , pkgHashCompilerABI = compilerAbiTag pkgConfigCompiler
4433 , pkgHashPlatform = pkgConfigPlatform
4434 , pkgHashFlagAssignment = elabFlagAssignment
4435 , pkgHashConfigureScriptArgs = elabConfigureScriptArgs
4436 , pkgHashVanillaLib = withVanillaLib
4437 , pkgHashSharedLib = withSharedLib
4438 , pkgHashDynExe = withDynExe
4439 , pkgHashFullyStaticExe = withFullyStaticExe
4440 , pkgHashGHCiLib = withGHCiLib
4441 , pkgHashProfLib = withProfLib
4442 , pkgHashProfExe = withProfExe
4443 , pkgHashProfLibDetail = withProfLibDetail
4444 , pkgHashProfExeDetail = withProfExeDetail
4445 , pkgHashCoverage = exeCoverage
4446 , pkgHashOptimization = withOptimization
4447 , pkgHashSplitSections = splitSections
4448 , pkgHashSplitObjs = splitObjs
4449 , pkgHashStripLibs = stripLibs
4450 , pkgHashStripExes = stripExes
4451 , pkgHashDebugInfo = withDebugInfo
4452 , pkgHashProgramArgs = elabProgramArgs
4453 , pkgHashExtraLibDirs = elabExtraLibDirs
4454 , pkgHashExtraLibDirsStatic = elabExtraLibDirsStatic
4455 , pkgHashExtraFrameworkDirs = elabExtraFrameworkDirs
4456 , pkgHashExtraIncludeDirs = elabExtraIncludeDirs
4457 , pkgHashProgPrefix = elabProgPrefix
4458 , pkgHashProgSuffix = elabProgSuffix
4459 , pkgHashPackageDbs = elabPackageDbs
4460 , pkgHashDocumentation = elabBuildHaddocks
4461 , pkgHashHaddockHoogle = elabHaddockHoogle
4462 , pkgHashHaddockHtml = elabHaddockHtml
4463 , pkgHashHaddockHtmlLocation = elabHaddockHtmlLocation
4464 , pkgHashHaddockForeignLibs = elabHaddockForeignLibs
4465 , pkgHashHaddockExecutables = elabHaddockExecutables
4466 , pkgHashHaddockTestSuites = elabHaddockTestSuites
4467 , pkgHashHaddockBenchmarks = elabHaddockBenchmarks
4468 , pkgHashHaddockInternal = elabHaddockInternal
4469 , pkgHashHaddockCss = elabHaddockCss
4470 , pkgHashHaddockLinkedSource = elabHaddockLinkedSource
4471 , pkgHashHaddockQuickJump = elabHaddockQuickJump
4472 , pkgHashHaddockContents = elabHaddockContents
4473 , pkgHashHaddockIndex = elabHaddockIndex
4474 , pkgHashHaddockBaseUrl = elabHaddockBaseUrl
4475 , pkgHashHaddockResourcesDir = elabHaddockResourcesDir
4476 , pkgHashHaddockOutputDir = elabHaddockOutputDir
4477 , pkgHashHaddockUseUnicode = elabHaddockUseUnicode
4479 where
4480 ElaboratedConfiguredPackage{..} = normaliseConfiguredPackage shared pkg
4481 LBC.BuildOptions{..} = elabBuildOptions
4483 -- | Given the 'InstalledPackageIndex' for a nix-style package store, and an
4484 -- 'ElaboratedInstallPlan', replace configured source packages by installed
4485 -- packages from the store whenever they exist.
4486 improveInstallPlanWithInstalledPackages
4487 :: Set UnitId
4488 -> ElaboratedInstallPlan
4489 -> ElaboratedInstallPlan
4490 improveInstallPlanWithInstalledPackages installedPkgIdSet =
4491 InstallPlan.installed canPackageBeImproved
4492 where
4493 canPackageBeImproved pkg =
4494 installedUnitId pkg `Set.member` installedPkgIdSet
4496 -- TODO: sanity checks:
4497 -- \* the installed package must have the expected deps etc
4498 -- \* the installed package must not be broken, valid dep closure
4500 -- TODO: decide what to do if we encounter broken installed packages,
4501 -- since overwriting is never safe.
4503 -- Path construction
4504 ------
4506 -- | The path to the directory that contains a specific executable.
4507 -- NB: For inplace NOT InstallPaths.bindir installDirs; for an
4508 -- inplace build those values are utter nonsense. So we
4509 -- have to guess where the directory is going to be.
4510 -- Fortunately this is "stable" part of Cabal API.
4511 -- But the way we get the build directory is A HORRIBLE
4512 -- HACK.
4513 binDirectoryFor
4514 :: DistDirLayout
4515 -> ElaboratedSharedConfig
4516 -> ElaboratedConfiguredPackage
4517 -> FilePath
4518 -> FilePath
4519 binDirectoryFor layout config package exe = case elabBuildStyle package of
4520 BuildAndInstall -> installedBinDirectory package
4521 BuildInplaceOnly{} -> inplaceBinRoot layout config package </> exe
4523 -- package has been built and installed.
4524 installedBinDirectory :: ElaboratedConfiguredPackage -> FilePath
4525 installedBinDirectory = InstallDirs.bindir . elabInstallDirs
4527 -- | The path to the @build@ directory for an inplace build.
4528 inplaceBinRoot
4529 :: DistDirLayout
4530 -> ElaboratedSharedConfig
4531 -> ElaboratedConfiguredPackage
4532 -> FilePath
4533 inplaceBinRoot layout config package =
4534 distBuildDirectory layout (elabDistDirParams config package)
4535 </> "build"
4537 --------------------------------------------------------------------------------
4538 -- Configure --coverage-for flags
4540 -- The list of non-pre-existing libraries without module holes, i.e. the
4541 -- main library and sub-libraries components of all the local packages in
4542 -- the project that are dependencies of the components being built and that do
4543 -- not require instantiations or are instantiations.
4544 determineCoverageFor
4545 :: ElaboratedConfiguredPackage
4546 -- ^ The package or component being configured
4547 -> ElaboratedInstallPlan
4548 -> Flag [UnitId]
4549 determineCoverageFor configuredPkg plan =
4550 Flag
4551 $ mapMaybe
4552 ( \case
4553 InstallPlan.Installed elab
4554 | shouldCoverPkg elab -> Just $ elabUnitId elab
4555 InstallPlan.Configured elab
4556 | shouldCoverPkg elab -> Just $ elabUnitId elab
4557 _ -> Nothing
4559 $ Graph.toList
4560 $ InstallPlan.toGraph plan
4561 where
4562 libDeps = elabLibDependencies configuredPkg
4563 shouldCoverPkg elab@ElaboratedConfiguredPackage{elabModuleShape, elabPkgSourceId = pkgSID, elabLocalToProject} =
4564 elabLocalToProject
4565 && not (isIndefiniteOrInstantiation elabModuleShape)
4566 -- TODO(#9493): We can only cover libraries in the same package
4567 -- as the testsuite
4568 && elabPkgSourceId configuredPkg == pkgSID
4569 -- Libraries only! We don't cover testsuite modules, so we never need
4570 -- the paths to their mix dirs. Furthermore, we do not install testsuites...
4571 && maybe False (\case CLibName{} -> True; CNotLibName{} -> False) (elabComponentName elab)
4572 -- We only want coverage for libraries which are dependencies of the given one
4573 && pkgSID `elem` map (confSrcId . fst) libDeps
4575 isIndefiniteOrInstantiation :: ModuleShape -> Bool
4576 isIndefiniteOrInstantiation = not . Set.null . modShapeRequires