Include the GHC "Project Unit Id" in the cabal store path
[cabal.git] / cabal-install / src / Distribution / Client / ProjectPlanning.hs
blobd5aedad0bb3c2adf0d65d647e2f87b77e3024ef5
1 {-# LANGUAGE CPP #-}
2 {-# LANGUAGE DeriveDataTypeable #-}
3 {-# LANGUAGE DeriveFunctor #-}
4 {-# LANGUAGE LambdaCase #-}
5 {-# LANGUAGE NamedFieldPuns #-}
6 {-# LANGUAGE RankNTypes #-}
7 {-# LANGUAGE RecordWildCards #-}
8 {-# LANGUAGE TypeFamilies #-}
10 -- |
11 -- /Elaborated: worked out with great care and nicety of detail; executed with great minuteness: elaborate preparations; elaborate care./
13 -- In this module we construct an install plan that includes all the information needed to execute it.
15 -- Building a project is therefore split into two phases:
17 -- 1. The construction of the install plan (which as far as possible should be pure), done here.
18 -- 2. The execution of the plan, done in "ProjectBuilding"
20 -- To achieve this we need a representation of this fully elaborated install plan; this representation
21 -- consists of two parts:
23 -- * A 'ElaboratedInstallPlan'. This is a 'GenericInstallPlan' with a
24 -- representation of source packages that includes a lot more detail about
25 -- that package's individual configuration
27 -- * A 'ElaboratedSharedConfig'. Some package configuration is the same for
28 -- every package in a plan. Rather than duplicate that info every entry in
29 -- the 'GenericInstallPlan' we keep that separately.
31 -- The division between the shared and per-package config is not set in stone
32 -- for all time. For example if we wanted to generalise the install plan to
33 -- describe a situation where we want to build some packages with GHC and some
34 -- with GHCJS then the platform and compiler would no longer be shared between
35 -- all packages but would have to be per-package (probably with some sanity
36 -- condition on the graph structure).
37 module Distribution.Client.ProjectPlanning
38 ( -- * Types for the elaborated install plan
39 ElaboratedInstallPlan
40 , ElaboratedConfiguredPackage (..)
41 , ElaboratedPlanPackage
42 , ElaboratedSharedConfig (..)
43 , ElaboratedReadyPackage
44 , BuildStyle (..)
45 , CabalFileText
47 -- * Reading the project configuration
48 -- $readingTheProjectConfiguration
49 , rebuildProjectConfig
51 -- * Producing the elaborated install plan
52 , rebuildInstallPlan
54 -- * Build targets
55 , availableTargets
56 , AvailableTarget (..)
57 , AvailableTargetStatus (..)
58 , TargetRequested (..)
59 , ComponentTarget (..)
60 , SubComponentTarget (..)
61 , showComponentTarget
62 , nubComponentTargets
64 -- * Selecting a plan subset
65 , pruneInstallPlanToTargets
66 , TargetAction (..)
67 , pruneInstallPlanToDependencies
68 , CannotPruneDependencies (..)
70 -- * Utils required for building
71 , pkgHasEphemeralBuildTargets
72 , elabBuildTargetWholeComponents
73 , configureCompiler
75 -- * Setup.hs CLI flags for building
76 , setupHsScriptOptions
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 Prelude ()
103 import Distribution.Client.Config
104 import Distribution.Client.Dependency
105 import Distribution.Client.DistDirLayout
106 import Distribution.Client.FetchUtils
107 import Distribution.Client.HashValue
108 import Distribution.Client.HttpUtils
109 import Distribution.Client.JobControl
110 import Distribution.Client.PackageHash
111 import Distribution.Client.ProjectConfig
112 import Distribution.Client.ProjectConfig.Legacy
113 import Distribution.Client.ProjectPlanOutput
114 import Distribution.Client.ProjectPlanning.SetupPolicy
115 ( NonSetupLibDepSolverPlanPackage (..)
116 , mkDefaultSetupDeps
117 , packageSetupScriptSpecVersion
118 , packageSetupScriptStyle
120 import Distribution.Client.ProjectPlanning.Types as Ty
121 import Distribution.Client.RebuildMonad
122 import Distribution.Client.Setup hiding (cabalVersion, packageName)
123 import Distribution.Client.SetupWrapper
124 import Distribution.Client.Store
125 import Distribution.Client.Targets (userToPackageConstraint)
126 import Distribution.Client.Types
127 import Distribution.Client.Utils (incVersion)
129 import qualified Distribution.Client.BuildReports.Storage as BuildReports
130 import qualified Distribution.Client.IndexUtils as IndexUtils
131 import qualified Distribution.Client.InstallPlan as InstallPlan
132 import qualified Distribution.Client.SolverInstallPlan as SolverInstallPlan
134 import Distribution.CabalSpecVersion
135 import Distribution.Utils.LogProgress
136 import Distribution.Utils.MapAccum
137 import Distribution.Utils.NubList
139 import qualified Hackage.Security.Client as Sec
141 import Distribution.Solver.Types.ConstraintSource
142 import Distribution.Solver.Types.InstSolverPackage
143 import Distribution.Solver.Types.LabeledPackageConstraint
144 import Distribution.Solver.Types.OptionalStanza
145 import Distribution.Solver.Types.PkgConfigDb
146 import Distribution.Solver.Types.Settings
147 import Distribution.Solver.Types.SolverId
148 import Distribution.Solver.Types.SolverPackage
149 import Distribution.Solver.Types.SourcePackage
151 import Distribution.ModuleName
152 import Distribution.Package
153 import Distribution.Simple.Compiler
154 import Distribution.Simple.Flag
155 import Distribution.Simple.LocalBuildInfo
156 ( Component (..)
157 , componentBuildInfo
158 , componentName
159 , pkgComponents
161 import Distribution.Simple.PackageIndex (InstalledPackageIndex)
162 import Distribution.Simple.Program
163 import Distribution.Simple.Program.Db
164 import Distribution.Simple.Program.Find
165 import Distribution.System
167 import Distribution.Types.AnnotatedId
168 import Distribution.Types.ComponentInclude
169 import Distribution.Types.ComponentName
170 import Distribution.Types.DumpBuildInfo
171 import Distribution.Types.GivenComponent
172 import Distribution.Types.LibraryName
173 import qualified Distribution.Types.LocalBuildConfig as LBC
174 import Distribution.Types.PackageVersionConstraint
175 import Distribution.Types.PkgconfigDependency
176 import Distribution.Types.UnqualComponentName
178 import Distribution.Backpack
179 import Distribution.Backpack.ComponentsGraph
180 import Distribution.Backpack.ConfiguredComponent
181 import Distribution.Backpack.FullUnitId
182 import Distribution.Backpack.LinkedComponent
183 import Distribution.Backpack.ModuleShape
185 import Distribution.Simple.Utils
186 import Distribution.Version
188 import qualified Distribution.InstalledPackageInfo as IPI
189 import qualified Distribution.PackageDescription as PD
190 import qualified Distribution.PackageDescription.Configuration as PD
191 import qualified Distribution.Simple.Configure as Cabal
192 import qualified Distribution.Simple.GHC as GHC
193 import qualified Distribution.Simple.GHCJS as GHCJS
194 import qualified Distribution.Simple.InstallDirs as InstallDirs
195 import qualified Distribution.Simple.LocalBuildInfo as Cabal
196 import qualified Distribution.Simple.Setup as Cabal
197 import qualified Distribution.Solver.Types.ComponentDeps as CD
199 import qualified Distribution.Compat.Graph as Graph
201 import Control.Exception (assert)
202 import Control.Monad (forM, sequence)
203 import Control.Monad.IO.Class (liftIO)
204 import Control.Monad.State as State (State, execState, runState, state)
205 import Data.Foldable (fold)
206 import Data.List (deleteBy, groupBy)
207 import qualified Data.List.NonEmpty as NE
208 import qualified Data.Map as Map
209 import qualified Data.Set as Set
210 import Distribution.Client.Errors
211 import System.FilePath
212 import Text.PrettyPrint (colon, comma, fsep, hang, punctuate, quotes, text, vcat, ($$))
213 import qualified Text.PrettyPrint as Disp
215 -- | Check that an 'ElaboratedConfiguredPackage' actually makes
216 -- sense under some 'ElaboratedSharedConfig'.
217 sanityCheckElaboratedConfiguredPackage
218 :: ElaboratedSharedConfig
219 -> ElaboratedConfiguredPackage
220 -> a
221 -> a
222 sanityCheckElaboratedConfiguredPackage
223 sharedConfig
224 elab@ElaboratedConfiguredPackage{..} =
225 ( case elabPkgOrComp of
226 ElabPackage pkg -> sanityCheckElaboratedPackage elab pkg
227 ElabComponent comp -> sanityCheckElaboratedComponent elab comp
229 -- The assertion below fails occasionally for unknown reason
230 -- so it was muted until we figure it out, otherwise it severely
231 -- hinders our ability to share and test development builds of cabal-install.
232 -- Tracking issue: https://github.com/haskell/cabal/issues/6006
234 -- either a package is being built inplace, or the
235 -- 'installedPackageId' we assigned is consistent with
236 -- the 'hashedInstalledPackageId' we would compute from
237 -- the elaborated configured package
238 . assert
239 ( isInplaceBuildStyle elabBuildStyle
240 || elabComponentId
241 == hashedInstalledPackageId
242 (packageHashInputs sharedConfig elab)
244 -- the stanzas explicitly disabled should not be available
245 . assert
246 ( optStanzaSetNull $
247 optStanzaKeysFilteredByValue (maybe False not) elabStanzasRequested `optStanzaSetIntersection` elabStanzasAvailable
249 -- either a package is built inplace, or we are not attempting to
250 -- build any test suites or benchmarks (we never build these
251 -- for remote packages!)
252 . assert
253 ( isInplaceBuildStyle elabBuildStyle
254 || optStanzaSetNull elabStanzasAvailable
257 sanityCheckElaboratedComponent
258 :: ElaboratedConfiguredPackage
259 -> ElaboratedComponent
260 -> a
261 -> a
262 sanityCheckElaboratedComponent
263 ElaboratedConfiguredPackage{..}
264 ElaboratedComponent{..} =
265 -- Should not be building bench or test if not inplace.
266 assert
267 ( isInplaceBuildStyle elabBuildStyle
268 || case compComponentName of
269 Nothing -> True
270 Just (CLibName _) -> True
271 Just (CExeName _) -> True
272 -- This is interesting: there's no way to declare a dependency
273 -- on a foreign library at the moment, but you may still want
274 -- to install these to the store
275 Just (CFLibName _) -> True
276 Just (CBenchName _) -> False
277 Just (CTestName _) -> False
280 sanityCheckElaboratedPackage
281 :: ElaboratedConfiguredPackage
282 -> ElaboratedPackage
283 -> a
284 -> a
285 sanityCheckElaboratedPackage
286 ElaboratedConfiguredPackage{..}
287 ElaboratedPackage{..} =
288 -- we should only have enabled stanzas that actually can be built
289 -- (according to the solver)
290 assert (pkgStanzasEnabled `optStanzaSetIsSubset` elabStanzasAvailable)
291 -- the stanzas that the user explicitly requested should be
292 -- enabled (by the previous test, they are also available)
293 . assert
294 ( optStanzaKeysFilteredByValue (fromMaybe False) elabStanzasRequested
295 `optStanzaSetIsSubset` pkgStanzasEnabled
298 -- $readingTheProjectConfiguration
300 -- The project configuration is assembled into a ProjectConfig as follows:
302 -- CLI arguments are converted using "commandLineFlagsToProjectConfig" in the
303 -- v2 command entrypoints and passed to "establishProjectBaseContext" which
304 -- then calls "rebuildProjectConfig".
306 -- "rebuildProjectConfig" then calls "readProjectConfig" to read the project
307 -- files. Due to the presence of conditionals, this output is in the form of a
308 -- "ProjectConfigSkeleton" and will be resolved by "rebuildProjectConfig" using
309 -- "instantiateProjectConfigSkeletonFetchingCompiler".
311 -- "readProjectConfig" also loads the global configuration, which is read with
312 -- "loadConfig" and convertd to a "ProjectConfig" with "convertLegacyGlobalConfig".
314 -- *Important:* You can notice how some project config options are needed to read the
315 -- project config! This is evident by the fact that "rebuildProjectConfig"
316 -- takes "HttpTransport" and "DistDirLayout" as parameters. Two arguments are
317 -- infact determined from the CLI alone (in "establishProjectBaseContext").
318 -- Consequently, project files (including global configuration) cannot
319 -- affect those parameters!
321 -- Furthermore, the project configuration can specify a compiler to use,
322 -- which we need to resolve the conditionals in the project configuration!
323 -- To solve this, we configure the compiler from what is obtained by applying
324 -- the CLI configuration over the the configuration obtained by "flattening"
325 -- ProjectConfigSkeleton. This means collapsing all conditionals by taking
326 -- both branches.
328 -- | Return the up-to-date project config and information about the local
329 -- packages within the project.
330 rebuildProjectConfig
331 :: Verbosity
332 -> HttpTransport
333 -> DistDirLayout
334 -> ProjectConfig
335 -> IO
336 ( ProjectConfig
337 , [PackageSpecifier UnresolvedSourcePackage]
339 rebuildProjectConfig
340 verbosity
341 httpTransport
342 distDirLayout@DistDirLayout
343 { distProjectRootDirectory
344 , distDirectory
345 , distProjectCacheFile
346 , distProjectCacheDirectory
347 , distProjectFile
349 cliConfig = do
350 progsearchpath <- liftIO $ getSystemSearchPath
352 let fileMonitorProjectConfig = newFileMonitor (distProjectCacheFile "config")
354 fileMonitorProjectConfigKey <- do
355 configPath <- getConfigFilePath projectConfigConfigFile
356 return
357 ( configPath
358 , distProjectFile ""
359 , (projectConfigHcFlavor, projectConfigHcPath, projectConfigHcPkg)
360 , progsearchpath
361 , packageConfigProgramPaths
362 , packageConfigProgramPathExtra
365 (projectConfig, localPackages) <-
366 runRebuild distProjectRootDirectory
367 $ rerunIfChanged
368 verbosity
369 fileMonitorProjectConfig
370 fileMonitorProjectConfigKey -- todo check deps too?
371 $ do
372 liftIO $ info verbosity "Project settings changed, reconfiguring..."
373 projectConfigSkeleton <- phaseReadProjectConfig
374 let fetchCompiler = do
375 -- have to create the cache directory before configuring the compiler
376 liftIO $ createDirectoryIfMissingVerbose verbosity True distProjectCacheDirectory
377 (compiler, Platform arch os, _) <- configureCompiler verbosity distDirLayout (fst (PD.ignoreConditions projectConfigSkeleton) <> cliConfig)
378 pure (os, arch, compilerInfo compiler)
380 projectConfig <- instantiateProjectConfigSkeletonFetchingCompiler fetchCompiler mempty projectConfigSkeleton
381 when (projectConfigDistDir (projectConfigShared $ projectConfig) /= NoFlag) $
382 liftIO $
383 warn verbosity "The builddir option is not supported in project and config files. It will be ignored."
384 localPackages <- phaseReadLocalPackages (projectConfig <> cliConfig)
385 return (projectConfig, localPackages)
387 info verbosity $
388 unlines $
389 ("this build was affected by the following (project) config files:" :) $
390 [ "- " ++ path
391 | Explicit path <- Set.toList $ projectConfigProvenance projectConfig
394 return (projectConfig <> cliConfig, localPackages)
395 where
396 ProjectConfigShared{projectConfigHcFlavor, projectConfigHcPath, projectConfigHcPkg, projectConfigIgnoreProject, projectConfigConfigFile} =
397 projectConfigShared cliConfig
399 PackageConfig{packageConfigProgramPaths, packageConfigProgramPathExtra} =
400 projectConfigLocalPackages cliConfig
402 -- Read the cabal.project (or implicit config) and combine it with
403 -- arguments from the command line
405 phaseReadProjectConfig :: Rebuild ProjectConfigSkeleton
406 phaseReadProjectConfig = do
407 readProjectConfig verbosity httpTransport projectConfigIgnoreProject projectConfigConfigFile distDirLayout
409 -- Look for all the cabal packages in the project
410 -- some of which may be local src dirs, tarballs etc
412 phaseReadLocalPackages
413 :: ProjectConfig
414 -> Rebuild [PackageSpecifier UnresolvedSourcePackage]
415 phaseReadLocalPackages
416 projectConfig@ProjectConfig
417 { projectConfigShared
418 , projectConfigBuildOnly
419 } = do
420 pkgLocations <- findProjectPackages distDirLayout projectConfig
421 -- Create folder only if findProjectPackages did not throw a
422 -- BadPackageLocations exception.
423 liftIO $ do
424 createDirectoryIfMissingVerbose verbosity True distDirectory
425 createDirectoryIfMissingVerbose verbosity True distProjectCacheDirectory
427 fetchAndReadSourcePackages
428 verbosity
429 distDirLayout
430 projectConfigShared
431 projectConfigBuildOnly
432 pkgLocations
434 configureCompiler
435 :: Verbosity
436 -> DistDirLayout
437 -> ProjectConfig
438 -> Rebuild (Compiler, Platform, ProgramDb)
439 configureCompiler
440 verbosity
441 DistDirLayout
442 { distProjectCacheFile
444 ProjectConfig
445 { projectConfigShared =
446 ProjectConfigShared
447 { projectConfigHcFlavor
448 , projectConfigHcPath
449 , projectConfigHcPkg
451 , projectConfigLocalPackages =
452 PackageConfig
453 { packageConfigProgramPaths
454 , packageConfigProgramPathExtra
456 } = do
457 let fileMonitorCompiler = newFileMonitor . distProjectCacheFile $ "compiler"
459 progsearchpath <- liftIO $ getSystemSearchPath
460 rerunIfChanged
461 verbosity
462 fileMonitorCompiler
463 ( hcFlavor
464 , hcPath
465 , hcPkg
466 , progsearchpath
467 , packageConfigProgramPaths
468 , packageConfigProgramPathExtra
470 $ do
471 liftIO $ info verbosity "Compiler settings changed, reconfiguring..."
472 progdb <- liftIO $ appendProgramSearchPath verbosity (fromNubList packageConfigProgramPathExtra) defaultProgramDb
473 let progdb' = userSpecifyPaths (Map.toList (getMapLast packageConfigProgramPaths)) progdb
474 result@(_, _, progdb'') <-
475 liftIO $
476 Cabal.configCompilerEx
477 hcFlavor
478 hcPath
479 hcPkg
480 progdb'
481 verbosity
483 -- Note that we added the user-supplied program locations and args
484 -- for /all/ programs, not just those for the compiler prog and
485 -- compiler-related utils. In principle we don't know which programs
486 -- the compiler will configure (and it does vary between compilers).
487 -- We do know however that the compiler will only configure the
488 -- programs it cares about, and those are the ones we monitor here.
489 monitorFiles (programsMonitorFiles progdb'')
491 return result
492 where
493 hcFlavor = flagToMaybe projectConfigHcFlavor
494 hcPath = flagToMaybe projectConfigHcPath
495 hcPkg = flagToMaybe projectConfigHcPkg
497 ------------------------------------------------------------------------------
499 -- * Deciding what to do: making an 'ElaboratedInstallPlan'
501 ------------------------------------------------------------------------------
503 -- | Return an up-to-date elaborated install plan.
505 -- Two variants of the install plan are returned: with and without packages
506 -- from the store. That is, the \"improved\" plan where source packages are
507 -- replaced by pre-existing installed packages from the store (when their ids
508 -- match), and also the original elaborated plan which uses primarily source
509 -- packages.
511 -- The improved plan is what we use for building, but the original elaborated
512 -- plan is useful for reporting and configuration. For example the @freeze@
513 -- command needs the source package info to know about flag choices and
514 -- dependencies of executables and setup scripts.
516 rebuildInstallPlan
517 :: Verbosity
518 -> DistDirLayout
519 -> CabalDirLayout
520 -> ProjectConfig
521 -> [PackageSpecifier UnresolvedSourcePackage]
522 -> Maybe InstalledPackageIndex
523 -> IO
524 ( ElaboratedInstallPlan -- with store packages
525 , ElaboratedInstallPlan -- with source packages
526 , ElaboratedSharedConfig
527 , IndexUtils.TotalIndexState
528 , IndexUtils.ActiveRepos
530 -- ^ @(improvedPlan, elaboratedPlan, _, _, _)@
531 rebuildInstallPlan
532 verbosity
533 distDirLayout@DistDirLayout
534 { distProjectRootDirectory
535 , distProjectCacheFile
537 CabalDirLayout
538 { cabalStoreDirLayout
539 } = \projectConfig localPackages mbInstalledPackages ->
540 runRebuild distProjectRootDirectory $ do
541 progsearchpath <- liftIO $ getSystemSearchPath
542 let projectConfigMonitored = projectConfig{projectConfigBuildOnly = mempty}
544 -- The overall improved plan is cached
545 rerunIfChanged
546 verbosity
547 fileMonitorImprovedPlan
548 -- react to changes in the project config,
549 -- the package .cabal files and the path
550 (projectConfigMonitored, localPackages, progsearchpath)
551 $ do
552 -- And so is the elaborated plan that the improved plan based on
553 (elaboratedPlan, elaboratedShared, totalIndexState, activeRepos) <-
554 rerunIfChanged
555 verbosity
556 fileMonitorElaboratedPlan
557 ( projectConfigMonitored
558 , localPackages
559 , progsearchpath
561 $ do
562 compilerEtc <- phaseConfigureCompiler projectConfig
563 _ <- phaseConfigurePrograms projectConfig compilerEtc
564 (solverPlan, pkgConfigDB, totalIndexState, activeRepos) <-
565 phaseRunSolver
566 projectConfig
567 compilerEtc
568 localPackages
569 (fromMaybe mempty mbInstalledPackages)
570 ( elaboratedPlan
571 , elaboratedShared
572 ) <-
573 phaseElaboratePlan
574 projectConfig
575 compilerEtc
576 pkgConfigDB
577 solverPlan
578 localPackages
580 phaseMaintainPlanOutputs elaboratedPlan elaboratedShared
581 return (elaboratedPlan, elaboratedShared, totalIndexState, activeRepos)
583 -- The improved plan changes each time we install something, whereas
584 -- the underlying elaborated plan only changes when input config
585 -- changes, so it's worth caching them separately.
586 improvedPlan <- phaseImprovePlan elaboratedPlan elaboratedShared
588 return (improvedPlan, elaboratedPlan, elaboratedShared, totalIndexState, activeRepos)
589 where
590 fileMonitorSolverPlan = newFileMonitorInCacheDir "solver-plan"
591 fileMonitorSourceHashes = newFileMonitorInCacheDir "source-hashes"
592 fileMonitorElaboratedPlan = newFileMonitorInCacheDir "elaborated-plan"
593 fileMonitorImprovedPlan = newFileMonitorInCacheDir "improved-plan"
595 newFileMonitorInCacheDir :: Eq a => FilePath -> FileMonitor a b
596 newFileMonitorInCacheDir = newFileMonitor . distProjectCacheFile
598 -- Configure the compiler we're using.
600 -- This is moderately expensive and doesn't change that often so we cache
601 -- it independently.
603 phaseConfigureCompiler
604 :: ProjectConfig
605 -> Rebuild (Compiler, Platform, ProgramDb)
606 phaseConfigureCompiler = configureCompiler verbosity distDirLayout
608 -- Configuring other programs.
610 -- Having configred the compiler, now we configure all the remaining
611 -- programs. This is to check we can find them, and to monitor them for
612 -- changes.
614 -- TODO: [required eventually] we don't actually do this yet.
616 -- We rely on the fact that the previous phase added the program config for
617 -- all local packages, but that all the programs configured so far are the
618 -- compiler program or related util programs.
620 phaseConfigurePrograms
621 :: ProjectConfig
622 -> (Compiler, Platform, ProgramDb)
623 -> Rebuild ()
624 phaseConfigurePrograms projectConfig (_, _, compilerprogdb) = do
625 -- Users are allowed to specify program locations independently for
626 -- each package (e.g. to use a particular version of a pre-processor
627 -- for some packages). However they cannot do this for the compiler
628 -- itself as that's just not going to work. So we check for this.
629 liftIO $
630 checkBadPerPackageCompilerPaths
631 (configuredPrograms compilerprogdb)
632 (getMapMappend (projectConfigSpecificPackage projectConfig))
634 -- TODO: [required eventually] find/configure other programs that the
635 -- user specifies.
637 -- TODO: [required eventually] find/configure all build-tools
638 -- but note that some of them may be built as part of the plan.
640 -- Run the solver to get the initial install plan.
641 -- This is expensive so we cache it independently.
643 phaseRunSolver
644 :: ProjectConfig
645 -> (Compiler, Platform, ProgramDb)
646 -> [PackageSpecifier UnresolvedSourcePackage]
647 -> InstalledPackageIndex
648 -> Rebuild (SolverInstallPlan, PkgConfigDb, IndexUtils.TotalIndexState, IndexUtils.ActiveRepos)
649 phaseRunSolver
650 projectConfig@ProjectConfig
651 { projectConfigShared
652 , projectConfigBuildOnly
654 (compiler, platform, progdb)
655 localPackages
656 installedPackages =
657 rerunIfChanged
658 verbosity
659 fileMonitorSolverPlan
660 ( solverSettings
661 , localPackages
662 , localPackagesEnabledStanzas
663 , compiler
664 , platform
665 , programDbSignature progdb
667 $ do
668 installedPkgIndex <-
669 getInstalledPackages
670 verbosity
671 compiler
672 progdb
673 platform
674 corePackageDbs
675 (sourcePkgDb, tis, ar) <-
676 getSourcePackages
677 verbosity
678 withRepoCtx
679 (solverSettingIndexState solverSettings)
680 (solverSettingActiveRepos solverSettings)
681 pkgConfigDB <- getPkgConfigDb verbosity progdb
683 -- TODO: [code cleanup] it'd be better if the Compiler contained the
684 -- ConfiguredPrograms that it needs, rather than relying on the progdb
685 -- since we don't need to depend on all the programs here, just the
686 -- ones relevant for the compiler.
688 liftIO $ do
689 notice verbosity "Resolving dependencies..."
690 planOrError <-
691 foldProgress logMsg (pure . Left) (pure . Right) $
692 planPackages
693 verbosity
694 compiler
695 platform
696 solverSettings
697 (installedPackages <> installedPkgIndex)
698 sourcePkgDb
699 pkgConfigDB
700 localPackages
701 localPackagesEnabledStanzas
702 case planOrError of
703 Left msg -> do
704 reportPlanningFailure projectConfig compiler platform localPackages
705 dieWithException verbosity $ PhaseRunSolverErr msg
706 Right plan -> return (plan, pkgConfigDB, tis, ar)
707 where
708 corePackageDbs :: [PackageDB]
709 corePackageDbs =
710 applyPackageDbFlags
711 [GlobalPackageDB]
712 (projectConfigPackageDBs projectConfigShared)
714 withRepoCtx :: (RepoContext -> IO a) -> IO a
715 withRepoCtx =
716 projectConfigWithSolverRepoContext
717 verbosity
718 projectConfigShared
719 projectConfigBuildOnly
721 solverSettings = resolveSolverSettings projectConfig
722 logMsg message rest = debugNoWrap verbosity message >> rest
724 localPackagesEnabledStanzas =
725 Map.fromList
726 [ (pkgname, stanzas)
727 | pkg <- localPackages
728 , -- TODO: misnomer: we should separate
729 -- builtin/global/inplace/local packages
730 -- and packages explicitly mentioned in the project
732 let pkgname = pkgSpecifierTarget pkg
733 testsEnabled =
734 lookupLocalPackageConfig
735 packageConfigTests
736 projectConfig
737 pkgname
738 benchmarksEnabled =
739 lookupLocalPackageConfig
740 packageConfigBenchmarks
741 projectConfig
742 pkgname
743 isLocal = isJust (shouldBeLocal pkg)
744 stanzas
745 | isLocal =
746 Map.fromList $
747 [ (TestStanzas, enabled)
748 | enabled <- flagToList testsEnabled
750 ++ [ (BenchStanzas, enabled)
751 | enabled <- flagToList benchmarksEnabled
753 | otherwise = Map.fromList [(TestStanzas, False), (BenchStanzas, False)]
756 -- Elaborate the solver's install plan to get a fully detailed plan. This
757 -- version of the plan has the final nix-style hashed ids.
759 phaseElaboratePlan
760 :: ProjectConfig
761 -> (Compiler, Platform, ProgramDb)
762 -> PkgConfigDb
763 -> SolverInstallPlan
764 -> [PackageSpecifier (SourcePackage (PackageLocation loc))]
765 -> Rebuild
766 ( ElaboratedInstallPlan
767 , ElaboratedSharedConfig
769 phaseElaboratePlan
770 ProjectConfig
771 { projectConfigShared
772 , projectConfigAllPackages
773 , projectConfigLocalPackages
774 , projectConfigSpecificPackage
775 , projectConfigBuildOnly
777 (compiler, platform, progdb)
778 pkgConfigDB
779 solverPlan
780 localPackages = do
781 liftIO $ debug verbosity "Elaborating the install plan..."
783 sourcePackageHashes <-
784 rerunIfChanged
785 verbosity
786 fileMonitorSourceHashes
787 (packageLocationsSignature solverPlan)
788 $ getPackageSourceHashes verbosity withRepoCtx solverPlan
790 defaultInstallDirs <- liftIO $ userInstallDirTemplates compiler
791 let installDirs = fmap Cabal.fromFlag $ (fmap Flag defaultInstallDirs) <> (projectConfigInstallDirs projectConfigShared)
792 (elaboratedPlan, elaboratedShared) <-
793 liftIO . runLogProgress verbosity $
794 elaborateInstallPlan
795 verbosity
796 platform
797 compiler
798 progdb
799 pkgConfigDB
800 distDirLayout
801 cabalStoreDirLayout
802 solverPlan
803 localPackages
804 sourcePackageHashes
805 installDirs
806 projectConfigShared
807 projectConfigAllPackages
808 projectConfigLocalPackages
809 (getMapMappend projectConfigSpecificPackage)
810 let instantiatedPlan =
811 instantiateInstallPlan
812 cabalStoreDirLayout
813 installDirs
814 elaboratedShared
815 elaboratedPlan
816 liftIO $ debugNoWrap verbosity (showElaboratedInstallPlan instantiatedPlan)
817 return (instantiatedPlan, elaboratedShared)
818 where
819 withRepoCtx :: (RepoContext -> IO a) -> IO a
820 withRepoCtx =
821 projectConfigWithSolverRepoContext
822 verbosity
823 projectConfigShared
824 projectConfigBuildOnly
826 -- Update the files we maintain that reflect our current build environment.
827 -- In particular we maintain a JSON representation of the elaborated
828 -- install plan (but not the improved plan since that reflects the state
829 -- of the build rather than just the input environment).
831 phaseMaintainPlanOutputs
832 :: ElaboratedInstallPlan
833 -> ElaboratedSharedConfig
834 -> Rebuild ()
835 phaseMaintainPlanOutputs elaboratedPlan elaboratedShared = liftIO $ do
836 debug verbosity "Updating plan.json"
837 writePlanExternalRepresentation
838 distDirLayout
839 elaboratedPlan
840 elaboratedShared
842 -- Improve the elaborated install plan. The elaborated plan consists
843 -- mostly of source packages (with full nix-style hashed ids). Where
844 -- corresponding installed packages already exist in the store, replace
845 -- them in the plan.
847 -- Note that we do monitor the store's package db here, so we will redo
848 -- this improvement phase when the db changes -- including as a result of
849 -- executing a plan and installing things.
851 phaseImprovePlan
852 :: ElaboratedInstallPlan
853 -> ElaboratedSharedConfig
854 -> Rebuild ElaboratedInstallPlan
855 phaseImprovePlan elaboratedPlan elaboratedShared = do
856 liftIO $ debug verbosity "Improving the install plan..."
857 storePkgIdSet <- getStoreEntries cabalStoreDirLayout compiler
858 let improvedPlan =
859 improveInstallPlanWithInstalledPackages
860 storePkgIdSet
861 elaboratedPlan
862 liftIO $ debugNoWrap verbosity (showElaboratedInstallPlan improvedPlan)
863 -- TODO: [nice to have] having checked which packages from the store
864 -- we're using, it may be sensible to sanity check those packages
865 -- by loading up the compiler package db and checking everything
866 -- matches up as expected, e.g. no dangling deps, files deleted.
867 return improvedPlan
868 where
869 compiler = pkgConfigCompiler elaboratedShared
871 -- | If a 'PackageSpecifier' refers to a single package, return Just that
872 -- package.
873 reportPlanningFailure :: ProjectConfig -> Compiler -> Platform -> [PackageSpecifier UnresolvedSourcePackage] -> IO ()
874 reportPlanningFailure projectConfig comp platform pkgSpecifiers =
875 when reportFailure $
876 BuildReports.storeLocal
877 (compilerInfo comp)
878 (fromNubList $ projectConfigSummaryFile . projectConfigBuildOnly $ projectConfig)
879 buildReports
880 platform
881 where
882 -- TODO may want to handle the projectConfigLogFile paramenter here, or just remove it entirely?
884 reportFailure = Cabal.fromFlag . projectConfigReportPlanningFailure . projectConfigBuildOnly $ projectConfig
885 pkgids = mapMaybe theSpecifiedPackage pkgSpecifiers
886 buildReports =
887 BuildReports.fromPlanningFailure
888 platform
889 (compilerId comp)
890 pkgids
891 -- TODO we may want to get more flag assignments and merge them here?
892 (packageConfigFlagAssignment . projectConfigAllPackages $ projectConfig)
894 theSpecifiedPackage :: Package pkg => PackageSpecifier pkg -> Maybe PackageId
895 theSpecifiedPackage pkgSpec =
896 case pkgSpec of
897 NamedPackage name [PackagePropertyVersion version] ->
898 PackageIdentifier name <$> trivialRange version
899 NamedPackage _ _ -> Nothing
900 SpecificSourcePackage pkg -> Just $ packageId pkg
901 -- \| If a range includes only a single version, return Just that version.
902 trivialRange :: VersionRange -> Maybe Version
903 trivialRange =
904 foldVersionRange
905 Nothing
906 Just -- "== v"
907 (\_ -> Nothing)
908 (\_ -> Nothing)
909 (\_ _ -> Nothing)
910 (\_ _ -> Nothing)
912 programsMonitorFiles :: ProgramDb -> [MonitorFilePath]
913 programsMonitorFiles progdb =
914 [ monitor
915 | prog <- configuredPrograms progdb
916 , monitor <-
917 monitorFileSearchPath
918 (programMonitorFiles prog)
919 (programPath prog)
922 -- | Select the bits of a 'ProgramDb' to monitor for value changes.
923 -- Use 'programsMonitorFiles' for the files to monitor.
924 programDbSignature :: ProgramDb -> [ConfiguredProgram]
925 programDbSignature progdb =
926 [ prog
927 { programMonitorFiles = []
928 , programOverrideEnv =
929 filter
930 ((/= "PATH") . fst)
931 (programOverrideEnv prog)
933 | prog <- configuredPrograms progdb
936 getInstalledPackages
937 :: Verbosity
938 -> Compiler
939 -> ProgramDb
940 -> Platform
941 -> PackageDBStack
942 -> Rebuild InstalledPackageIndex
943 getInstalledPackages verbosity compiler progdb platform packagedbs = do
944 monitorFiles . map monitorFileOrDirectory
945 =<< liftIO
946 ( IndexUtils.getInstalledPackagesMonitorFiles
947 verbosity
948 compiler
949 packagedbs
950 progdb
951 platform
953 liftIO $
954 IndexUtils.getInstalledPackages
955 verbosity
956 compiler
957 packagedbs
958 progdb
961 --TODO: [nice to have] use this but for sanity / consistency checking
962 getPackageDBContents :: Verbosity
963 -> Compiler -> ProgramDb -> Platform
964 -> PackageDB
965 -> Rebuild InstalledPackageIndex
966 getPackageDBContents verbosity compiler progdb platform packagedb = do
967 monitorFiles . map monitorFileOrDirectory
968 =<< liftIO (IndexUtils.getInstalledPackagesMonitorFiles
969 verbosity compiler
970 [packagedb] progdb platform)
971 liftIO $ do
972 createPackageDBIfMissing verbosity compiler progdb packagedb
973 Cabal.getPackageDBContents verbosity compiler
974 packagedb progdb
977 getSourcePackages
978 :: Verbosity
979 -> (forall a. (RepoContext -> IO a) -> IO a)
980 -> Maybe IndexUtils.TotalIndexState
981 -> Maybe IndexUtils.ActiveRepos
982 -> Rebuild (SourcePackageDb, IndexUtils.TotalIndexState, IndexUtils.ActiveRepos)
983 getSourcePackages verbosity withRepoCtx idxState activeRepos = do
984 (sourcePkgDbWithTIS, repos) <-
985 liftIO $
986 withRepoCtx $ \repoctx -> do
987 sourcePkgDbWithTIS <- IndexUtils.getSourcePackagesAtIndexState verbosity repoctx idxState activeRepos
988 return (sourcePkgDbWithTIS, repoContextRepos repoctx)
990 traverse_ needIfExists
991 . IndexUtils.getSourcePackagesMonitorFiles
992 $ repos
993 return sourcePkgDbWithTIS
995 getPkgConfigDb :: Verbosity -> ProgramDb -> Rebuild PkgConfigDb
996 getPkgConfigDb verbosity progdb = do
997 dirs <- liftIO $ getPkgConfigDbDirs verbosity progdb
998 -- Just monitor the dirs so we'll notice new .pc files.
999 -- Alternatively we could monitor all the .pc files too.
1000 traverse_ monitorDirectoryStatus dirs
1001 liftIO $ readPkgConfigDb verbosity progdb
1003 -- | Select the config values to monitor for changes package source hashes.
1004 packageLocationsSignature
1005 :: SolverInstallPlan
1006 -> [(PackageId, PackageLocation (Maybe FilePath))]
1007 packageLocationsSignature solverPlan =
1008 [ (packageId pkg, srcpkgSource pkg)
1009 | SolverInstallPlan.Configured (SolverPackage{solverPkgSource = pkg}) <-
1010 SolverInstallPlan.toList solverPlan
1013 -- | Get the 'HashValue' for all the source packages where we use hashes,
1014 -- and download any packages required to do so.
1016 -- Note that we don't get hashes for local unpacked packages.
1017 getPackageSourceHashes
1018 :: Verbosity
1019 -> (forall a. (RepoContext -> IO a) -> IO a)
1020 -> SolverInstallPlan
1021 -> Rebuild (Map PackageId PackageSourceHash)
1022 getPackageSourceHashes verbosity withRepoCtx solverPlan = do
1023 -- Determine if and where to get the package's source hash from.
1025 let allPkgLocations :: [(PackageId, PackageLocation (Maybe FilePath))]
1026 allPkgLocations =
1027 [ (packageId pkg, srcpkgSource pkg)
1028 | SolverInstallPlan.Configured (SolverPackage{solverPkgSource = pkg}) <-
1029 SolverInstallPlan.toList solverPlan
1032 -- Tarballs that were local in the first place.
1033 -- We'll hash these tarball files directly.
1034 localTarballPkgs :: [(PackageId, FilePath)]
1035 localTarballPkgs =
1036 [ (pkgid, tarball)
1037 | (pkgid, LocalTarballPackage tarball) <- allPkgLocations
1040 -- Tarballs from remote URLs. We must have downloaded these already
1041 -- (since we extracted the .cabal file earlier)
1042 remoteTarballPkgs =
1043 [ (pkgid, tarball)
1044 | (pkgid, RemoteTarballPackage _ (Just tarball)) <- allPkgLocations
1047 -- tarballs from source-repository-package stanzas
1048 sourceRepoTarballPkgs =
1049 [ (pkgid, tarball)
1050 | (pkgid, RemoteSourceRepoPackage _ (Just tarball)) <- allPkgLocations
1053 -- Tarballs from repositories, either where the repository provides
1054 -- hashes as part of the repo metadata, or where we will have to
1055 -- download and hash the tarball.
1056 repoTarballPkgsWithMetadataUnvalidated :: [(PackageId, Repo)]
1057 repoTarballPkgsWithoutMetadata :: [(PackageId, Repo)]
1058 ( repoTarballPkgsWithMetadataUnvalidated
1059 , repoTarballPkgsWithoutMetadata
1061 partitionEithers
1062 [ case repo of
1063 RepoSecure{} -> Left (pkgid, repo)
1064 _ -> Right (pkgid, repo)
1065 | (pkgid, RepoTarballPackage repo _ _) <- allPkgLocations
1068 (repoTarballPkgsWithMetadata, repoTarballPkgsToDownloadWithMeta) <- fmap partitionEithers $
1069 liftIO $
1070 withRepoCtx $ \repoctx -> forM repoTarballPkgsWithMetadataUnvalidated $
1071 \x@(pkg, repo) ->
1072 verifyFetchedTarball verbosity repoctx repo pkg >>= \b -> case b of
1073 True -> return $ Left x
1074 False -> return $ Right x
1076 -- For tarballs from repos that do not have hashes available we now have
1077 -- to check if the packages were downloaded already.
1079 ( repoTarballPkgsToDownloadWithNoMeta
1080 , repoTarballPkgsDownloaded
1081 ) <-
1082 fmap partitionEithers $
1083 liftIO $
1084 sequence
1085 [ do
1086 mtarball <- checkRepoTarballFetched repo pkgid
1087 case mtarball of
1088 Nothing -> return (Left (pkgid, repo))
1089 Just tarball -> return (Right (pkgid, tarball))
1090 | (pkgid, repo) <- repoTarballPkgsWithoutMetadata
1093 let repoTarballPkgsToDownload = repoTarballPkgsToDownloadWithMeta ++ repoTarballPkgsToDownloadWithNoMeta
1094 ( hashesFromRepoMetadata
1095 , repoTarballPkgsNewlyDownloaded
1096 ) <-
1097 -- Avoid having to initialise the repository (ie 'withRepoCtx') if we
1098 -- don't have to. (The main cost is configuring the http client.)
1099 if null repoTarballPkgsToDownload && null repoTarballPkgsWithMetadata
1100 then return (Map.empty, [])
1101 else liftIO $ withRepoCtx $ \repoctx -> do
1102 -- For tarballs from repos that do have hashes available as part of the
1103 -- repo metadata we now load up the index for each repo and retrieve
1104 -- the hashes for the packages
1106 hashesFromRepoMetadata <-
1107 Sec.uncheckClientErrors $ -- TODO: [code cleanup] wrap in our own exceptions
1108 fmap (Map.fromList . concat) $
1109 sequence
1110 -- Reading the repo index is expensive so we group the packages by repo
1111 [ repoContextWithSecureRepo repoctx repo $ \secureRepo ->
1112 Sec.withIndex secureRepo $ \repoIndex ->
1113 sequence
1114 [ do
1115 hash <-
1116 Sec.trusted
1117 <$> Sec.indexLookupHash repoIndex pkgid -- strip off Trusted tag
1119 -- Note that hackage-security currently uses SHA256
1120 -- but this API could in principle give us some other
1121 -- choice in future.
1122 return (pkgid, hashFromTUF hash)
1123 | pkgid <- pkgids
1125 | (repo, pkgids) <-
1126 map (\grp@((_, repo) :| _) -> (repo, map fst (NE.toList grp)))
1127 . NE.groupBy ((==) `on` (remoteRepoName . repoRemote . snd))
1128 . sortBy (compare `on` (remoteRepoName . repoRemote . snd))
1129 $ repoTarballPkgsWithMetadata
1132 -- For tarballs from repos that do not have hashes available, download
1133 -- the ones we previously determined we need.
1135 repoTarballPkgsNewlyDownloaded <-
1136 sequence
1137 [ do
1138 tarball <- fetchRepoTarball verbosity repoctx repo pkgid
1139 return (pkgid, tarball)
1140 | (pkgid, repo) <- repoTarballPkgsToDownload
1143 return
1144 ( hashesFromRepoMetadata
1145 , repoTarballPkgsNewlyDownloaded
1148 -- Hash tarball files for packages where we have to do that. This includes
1149 -- tarballs that were local in the first place, plus tarballs from repos,
1150 -- either previously cached or freshly downloaded.
1152 let allTarballFilePkgs :: [(PackageId, FilePath)]
1153 allTarballFilePkgs =
1154 localTarballPkgs
1155 ++ remoteTarballPkgs
1156 ++ sourceRepoTarballPkgs
1157 ++ repoTarballPkgsDownloaded
1158 ++ repoTarballPkgsNewlyDownloaded
1159 hashesFromTarballFiles <-
1160 liftIO $
1161 fmap Map.fromList $
1162 sequence
1163 [ do
1164 srchash <- readFileHashValue tarball
1165 return (pkgid, srchash)
1166 | (pkgid, tarball) <- allTarballFilePkgs
1168 monitorFiles
1169 [ monitorFile tarball
1170 | (_pkgid, tarball) <- allTarballFilePkgs
1173 -- Return the combination
1174 return $!
1175 hashesFromRepoMetadata
1176 <> hashesFromTarballFiles
1178 -- | Append the given package databases to an existing PackageDBStack.
1179 -- A @Nothing@ entry will clear everything before it.
1180 applyPackageDbFlags :: PackageDBStack -> [Maybe PackageDB] -> PackageDBStack
1181 applyPackageDbFlags dbs' [] = dbs'
1182 applyPackageDbFlags _ (Nothing : dbs) = applyPackageDbFlags [] dbs
1183 applyPackageDbFlags dbs' (Just db : dbs) = applyPackageDbFlags (dbs' ++ [db]) dbs
1185 -- ------------------------------------------------------------
1187 -- * Installation planning
1189 -- ------------------------------------------------------------
1191 planPackages
1192 :: Verbosity
1193 -> Compiler
1194 -> Platform
1195 -> SolverSettings
1196 -> InstalledPackageIndex
1197 -> SourcePackageDb
1198 -> PkgConfigDb
1199 -> [PackageSpecifier UnresolvedSourcePackage]
1200 -> Map PackageName (Map OptionalStanza Bool)
1201 -> Progress String String SolverInstallPlan
1202 planPackages
1203 verbosity
1204 comp
1205 platform
1206 SolverSettings{..}
1207 installedPkgIndex
1208 sourcePkgDb
1209 pkgConfigDB
1210 localPackages
1211 pkgStanzasEnable =
1212 resolveDependencies
1213 platform
1214 (compilerInfo comp)
1215 pkgConfigDB
1216 resolverParams
1217 where
1218 -- TODO: [nice to have] disable multiple instances restriction in
1219 -- the solver, but then make sure we can cope with that in the
1220 -- output.
1221 resolverParams :: DepResolverParams
1222 resolverParams =
1223 setMaxBackjumps solverSettingMaxBackjumps
1224 . setIndependentGoals solverSettingIndependentGoals
1225 . setReorderGoals solverSettingReorderGoals
1226 . setCountConflicts solverSettingCountConflicts
1227 . setFineGrainedConflicts solverSettingFineGrainedConflicts
1228 . setMinimizeConflictSet solverSettingMinimizeConflictSet
1229 -- TODO: [required eventually] should only be configurable for
1230 -- custom installs
1231 -- . setAvoidReinstalls solverSettingAvoidReinstalls
1233 -- TODO: [required eventually] should only be configurable for
1234 -- custom installs
1235 -- . setShadowPkgs solverSettingShadowPkgs
1237 . setStrongFlags solverSettingStrongFlags
1238 . setAllowBootLibInstalls solverSettingAllowBootLibInstalls
1239 . setOnlyConstrained solverSettingOnlyConstrained
1240 . setSolverVerbosity verbosity
1241 -- TODO: [required eventually] decide if we need to prefer
1242 -- installed for global packages, or prefer latest even for
1243 -- global packages. Perhaps should be configurable but with a
1244 -- different name than "upgrade-dependencies".
1245 . setPreferenceDefault
1246 ( if Cabal.asBool solverSettingPreferOldest
1247 then PreferAllOldest
1248 else PreferLatestForSelected
1250 {-(if solverSettingUpgradeDeps
1251 then PreferAllLatest
1252 else PreferLatestForSelected)-}
1254 . removeLowerBounds solverSettingAllowOlder
1255 . removeUpperBounds solverSettingAllowNewer
1256 . addDefaultSetupDependencies
1257 ( mkDefaultSetupDeps comp platform
1258 . PD.packageDescription
1259 . srcpkgDescription
1261 . addSetupCabalMinVersionConstraint setupMinCabalVersionConstraint
1262 . addSetupCabalMaxVersionConstraint setupMaxCabalVersionConstraint
1263 . addPreferences
1264 -- preferences from the config file or command line
1265 [ PackageVersionPreference name ver
1266 | PackageVersionConstraint name ver <- solverSettingPreferences
1268 . addConstraints
1269 -- version constraints from the config file or command line
1270 [ LabeledPackageConstraint (userToPackageConstraint pc) src
1271 | (pc, src) <- solverSettingConstraints
1273 . addPreferences
1274 -- enable stanza preference unilaterally, regardless if the user asked
1275 -- accordingly or expressed no preference, to help hint the solver
1276 [ PackageStanzasPreference pkgname stanzas
1277 | pkg <- localPackages
1278 , let pkgname = pkgSpecifierTarget pkg
1279 stanzaM = Map.findWithDefault Map.empty pkgname pkgStanzasEnable
1280 stanzas =
1281 [ stanza | stanza <- [minBound .. maxBound], Map.lookup stanza stanzaM /= Just False
1283 , not (null stanzas)
1285 . addConstraints
1286 -- enable stanza constraints where the user asked to enable
1287 [ LabeledPackageConstraint
1288 ( PackageConstraint
1289 (scopeToplevel pkgname)
1290 (PackagePropertyStanzas stanzas)
1292 ConstraintSourceConfigFlagOrTarget
1293 | pkg <- localPackages
1294 , let pkgname = pkgSpecifierTarget pkg
1295 stanzaM = Map.findWithDefault Map.empty pkgname pkgStanzasEnable
1296 stanzas =
1297 [ stanza | stanza <- [minBound .. maxBound], Map.lookup stanza stanzaM == Just True
1299 , not (null stanzas)
1301 . addConstraints
1302 -- TODO: [nice to have] should have checked at some point that the
1303 -- package in question actually has these flags.
1304 [ LabeledPackageConstraint
1305 ( PackageConstraint
1306 (scopeToplevel pkgname)
1307 (PackagePropertyFlags flags)
1309 ConstraintSourceConfigFlagOrTarget
1310 | (pkgname, flags) <- Map.toList solverSettingFlagAssignments
1312 . addConstraints
1313 -- TODO: [nice to have] we have user-supplied flags for unspecified
1314 -- local packages (as well as specific per-package flags). For the
1315 -- former we just apply all these flags to all local targets which
1316 -- is silly. We should check if the flags are appropriate.
1317 [ LabeledPackageConstraint
1318 ( PackageConstraint
1319 (scopeToplevel pkgname)
1320 (PackagePropertyFlags flags)
1322 ConstraintSourceConfigFlagOrTarget
1323 | let flags = solverSettingFlagAssignment
1324 , not (PD.nullFlagAssignment flags)
1325 , pkg <- localPackages
1326 , let pkgname = pkgSpecifierTarget pkg
1328 $ stdResolverParams
1330 stdResolverParams :: DepResolverParams
1331 stdResolverParams =
1332 -- Note: we don't use the standardInstallPolicy here, since that uses
1333 -- its own addDefaultSetupDependencies that is not appropriate for us.
1334 basicInstallPolicy
1335 installedPkgIndex
1336 sourcePkgDb
1337 localPackages
1339 -- While we can talk to older Cabal versions (we need to be able to
1340 -- do so for custom Setup scripts that require older Cabal lib
1341 -- versions), we have problems talking to some older versions that
1342 -- don't support certain features.
1344 -- For example, Cabal-1.16 and older do not know about build targets.
1345 -- Even worse, 1.18 and older only supported the --constraint flag
1346 -- with source package ids, not --dependency with installed package
1347 -- ids. That is bad because we cannot reliably select the right
1348 -- dependencies in the presence of multiple instances (i.e. the
1349 -- store). See issue #3932. So we require Cabal 1.20 as a minimum.
1351 -- Moreover, lib:Cabal generally only supports the interface of
1352 -- current and past compilers; in fact recent lib:Cabal versions
1353 -- will warn when they encounter a too new or unknown GHC compiler
1354 -- version (c.f. #415). To avoid running into unsupported
1355 -- configurations we encode the compatibility matrix as lower
1356 -- bounds on lib:Cabal here (effectively corresponding to the
1357 -- respective major Cabal version bundled with the respective GHC
1358 -- release).
1360 -- GHC 9.2 needs Cabal >= 3.6
1361 -- GHC 9.0 needs Cabal >= 3.4
1362 -- GHC 8.10 needs Cabal >= 3.2
1363 -- GHC 8.8 needs Cabal >= 3.0
1364 -- GHC 8.6 needs Cabal >= 2.4
1365 -- GHC 8.4 needs Cabal >= 2.2
1366 -- GHC 8.2 needs Cabal >= 2.0
1367 -- GHC 8.0 needs Cabal >= 1.24
1368 -- GHC 7.10 needs Cabal >= 1.22
1370 -- (NB: we don't need to consider older GHCs as Cabal >= 1.20 is
1371 -- the absolute lower bound)
1373 -- TODO: long-term, this compatibility matrix should be
1374 -- stored as a field inside 'Distribution.Compiler.Compiler'
1375 setupMinCabalVersionConstraint
1376 | isGHC, compVer >= mkVersion [9, 6] = mkVersion [3, 10]
1377 | isGHC, compVer >= mkVersion [9, 4] = mkVersion [3, 8]
1378 | isGHC, compVer >= mkVersion [9, 2] = mkVersion [3, 6]
1379 | isGHC, compVer >= mkVersion [9, 0] = mkVersion [3, 4]
1380 | isGHC, compVer >= mkVersion [8, 10] = mkVersion [3, 2]
1381 | isGHC, compVer >= mkVersion [8, 8] = mkVersion [3, 0]
1382 | isGHC, compVer >= mkVersion [8, 6] = mkVersion [2, 4]
1383 | isGHC, compVer >= mkVersion [8, 4] = mkVersion [2, 2]
1384 | isGHC, compVer >= mkVersion [8, 2] = mkVersion [2, 0]
1385 | isGHC, compVer >= mkVersion [8, 0] = mkVersion [1, 24]
1386 | isGHC, compVer >= mkVersion [7, 10] = mkVersion [1, 22]
1387 | otherwise = mkVersion [1, 20]
1388 where
1389 isGHC = compFlav `elem` [GHC, GHCJS]
1390 compFlav = compilerFlavor comp
1391 compVer = compilerVersion comp
1393 -- As we can't predict the future, we also place a global upper
1394 -- bound on the lib:Cabal version we know how to interact with:
1396 -- The upper bound is computed by incrementing the current major
1397 -- version twice in order to allow for the current version, as
1398 -- well as the next adjacent major version (one of which will not
1399 -- be released, as only "even major" versions of Cabal are
1400 -- released to Hackage or bundled with proper GHC releases).
1402 -- For instance, if the current version of cabal-install is an odd
1403 -- development version, e.g. Cabal-2.1.0.0, then we impose an
1404 -- upper bound `setup.Cabal < 2.3`; if `cabal-install` is on a
1405 -- stable/release even version, e.g. Cabal-2.2.1.0, the upper
1406 -- bound is `setup.Cabal < 2.4`. This gives us enough flexibility
1407 -- when dealing with development snapshots of Cabal and cabal-install.
1409 setupMaxCabalVersionConstraint =
1410 alterVersion (take 2) $ incVersion 1 $ incVersion 1 cabalVersion
1412 ------------------------------------------------------------------------------
1414 -- * Install plan post-processing
1416 ------------------------------------------------------------------------------
1418 -- This phase goes from the InstallPlan we get from the solver and has to
1419 -- make an elaborated install plan.
1421 -- We go in two steps:
1423 -- 1. elaborate all the source packages that the solver has chosen.
1424 -- 2. swap source packages for pre-existing installed packages wherever
1425 -- possible.
1427 -- We do it in this order, elaborating and then replacing, because the easiest
1428 -- way to calculate the installed package ids used for the replacement step is
1429 -- from the elaborated configuration for each package.
1431 ------------------------------------------------------------------------------
1433 -- * Install plan elaboration
1435 ------------------------------------------------------------------------------
1437 -- Note [SolverId to ConfiguredId]
1438 -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
1439 -- Dependency solving is a per package affair, so after we're done, we
1440 -- end up with 'SolverInstallPlan' that records in 'solverPkgLibDeps'
1441 -- and 'solverPkgExeDeps' what packages provide the libraries and executables
1442 -- needed by each component of the package (phew!) For example, if I have
1444 -- library
1445 -- build-depends: lib
1446 -- build-tool-depends: pkg:exe1
1447 -- build-tools: alex
1449 -- After dependency solving, I find out that this library component has
1450 -- library dependencies on lib-0.2, and executable dependencies on pkg-0.1
1451 -- and alex-0.3 (other components of the package may have different
1452 -- dependencies). Note that I've "lost" the knowledge that I depend
1454 -- * specifically* on the exe1 executable from pkg.
1457 -- So, we have a this graph of packages, and we need to transform it into
1458 -- a graph of components which we are actually going to build. In particular:
1460 -- NODE changes from PACKAGE (SolverPackage) to COMPONENTS (ElaboratedConfiguredPackage)
1461 -- EDGE changes from PACKAGE DEP (SolverId) to COMPONENT DEPS (ConfiguredId)
1463 -- In both cases, what was previously a single node/edge may turn into multiple
1464 -- nodes/edges. Multiple components, because there may be multiple components
1465 -- in a package; multiple component deps, because we may depend upon multiple
1466 -- executables from the same package (and maybe, some day, multiple libraries
1467 -- from the same package.)
1469 -- Let's talk about how to do this transformation. Naively, we might consider
1470 -- just processing each package, converting it into (zero or) one or more
1471 -- components. But we also have to update the edges; this leads to
1472 -- two complications:
1474 -- 1. We don't know what the ConfiguredId of a component is until
1475 -- we've configured it, but we cannot configure a component unless
1476 -- we know the ConfiguredId of all its dependencies. Thus, we must
1477 -- process the 'SolverInstallPlan' in topological order.
1479 -- 2. When we process a package, we know the SolverIds of its
1480 -- dependencies, but we have to do some work to turn these into
1481 -- ConfiguredIds. For example, in the case of build-tool-depends, the
1482 -- SolverId isn't enough to uniquely determine the ConfiguredId we should
1483 -- elaborate to: we have to look at the executable name attached to
1484 -- the package name in the package description to figure it out.
1485 -- At the same time, we NEED to use the SolverId, because there might
1486 -- be multiple versions of the same package in the build plan
1487 -- (due to setup dependencies); we can't just look up the package name
1488 -- from the package description.
1490 -- We can adopt the following strategy:
1492 -- * When a package is transformed into components, record
1493 -- a mapping from SolverId to ALL of the components
1494 -- which were elaborated.
1496 -- * When we look up an edge, we use our knowledge of the
1497 -- component name to *filter* the list of components into
1498 -- the ones we actually wanted to refer to.
1500 -- By the way, we can tell that SolverInstallPlan is not the "right" type
1501 -- because a SolverId cannot adequately represent all possible dependency
1502 -- solver states: we may need to record foo-0.1 multiple times in
1503 -- the solver install plan with different dependencies. This imprecision in the
1504 -- type currently doesn't cause any problems because the dependency solver
1505 -- continues to enforce the single instance restriction regardless of compiler
1506 -- version. The right way to solve this is to come up with something very much
1507 -- like a 'ConfiguredId', in that it incorporates the version choices of its
1508 -- dependencies, but less fine grained.
1510 -- | Produce an elaborated install plan using the policy for local builds with
1511 -- a nix-style shared store.
1513 -- In theory should be able to make an elaborated install plan with a policy
1514 -- matching that of the classic @cabal install --user@ or @--global@
1515 elaborateInstallPlan
1516 :: Verbosity
1517 -> Platform
1518 -> Compiler
1519 -> ProgramDb
1520 -> PkgConfigDb
1521 -> DistDirLayout
1522 -> StoreDirLayout
1523 -> SolverInstallPlan
1524 -> [PackageSpecifier (SourcePackage (PackageLocation loc))]
1525 -> Map PackageId PackageSourceHash
1526 -> InstallDirs.InstallDirTemplates
1527 -> ProjectConfigShared
1528 -> PackageConfig
1529 -> PackageConfig
1530 -> Map PackageName PackageConfig
1531 -> LogProgress (ElaboratedInstallPlan, ElaboratedSharedConfig)
1532 elaborateInstallPlan
1533 verbosity
1534 platform
1535 compiler
1536 compilerprogdb
1537 pkgConfigDB
1538 distDirLayout@DistDirLayout{..}
1539 storeDirLayout@StoreDirLayout{storePackageDBStack}
1540 solverPlan
1541 localPackages
1542 sourcePackageHashes
1543 defaultInstallDirs
1544 sharedPackageConfig
1545 allPackagesConfig
1546 localPackagesConfig
1547 perPackageConfig = do
1548 x <- elaboratedInstallPlan
1549 return (x, elaboratedSharedConfig)
1550 where
1551 elaboratedSharedConfig =
1552 ElaboratedSharedConfig
1553 { pkgConfigPlatform = platform
1554 , pkgConfigCompiler = compiler
1555 , pkgConfigCompilerProgs = compilerprogdb
1556 , pkgConfigReplOptions = mempty
1559 preexistingInstantiatedPkgs :: Map UnitId FullUnitId
1560 preexistingInstantiatedPkgs =
1561 Map.fromList (mapMaybe f (SolverInstallPlan.toList solverPlan))
1562 where
1563 f (SolverInstallPlan.PreExisting inst)
1564 | let ipkg = instSolverPkgIPI inst
1565 , not (IPI.indefinite ipkg) =
1566 Just
1567 ( IPI.installedUnitId ipkg
1568 , ( FullUnitId
1569 (IPI.installedComponentId ipkg)
1570 (Map.fromList (IPI.instantiatedWith ipkg))
1573 f _ = Nothing
1575 elaboratedInstallPlan
1576 :: LogProgress (InstallPlan.GenericInstallPlan IPI.InstalledPackageInfo ElaboratedConfiguredPackage)
1577 elaboratedInstallPlan =
1578 flip InstallPlan.fromSolverInstallPlanWithProgress solverPlan $ \mapDep planpkg ->
1579 case planpkg of
1580 SolverInstallPlan.PreExisting pkg ->
1581 return [InstallPlan.PreExisting (instSolverPkgIPI pkg)]
1582 SolverInstallPlan.Configured pkg ->
1583 let inplace_doc
1584 | shouldBuildInplaceOnly pkg = text "inplace"
1585 | otherwise = Disp.empty
1586 in addProgressCtx
1587 ( text "In the"
1588 <+> inplace_doc
1589 <+> text "package"
1590 <+> quotes (pretty (packageId pkg))
1592 $ map InstallPlan.Configured <$> elaborateSolverToComponents mapDep pkg
1594 -- NB: We don't INSTANTIATE packages at this point. That's
1595 -- a post-pass. This makes it simpler to compute dependencies.
1596 elaborateSolverToComponents
1597 :: (SolverId -> [ElaboratedPlanPackage])
1598 -> SolverPackage UnresolvedPkgLoc
1599 -> LogProgress [ElaboratedConfiguredPackage]
1600 elaborateSolverToComponents mapDep spkg@(SolverPackage _ _ _ deps0 exe_deps0) =
1601 case mkComponentsGraph (elabEnabledSpec elab0) pd of
1602 Right g -> do
1603 let src_comps = componentsGraphToList g
1604 infoProgress $
1605 hang
1606 (text "Component graph for" <+> pretty pkgid <<>> colon)
1608 (dispComponentsWithDeps src_comps)
1609 (_, comps) <-
1610 mapAccumM
1611 buildComponent
1612 (Map.empty, Map.empty, Map.empty)
1613 (map fst src_comps)
1614 let not_per_component_reasons = why_not_per_component src_comps
1615 if null not_per_component_reasons
1616 then return comps
1617 else do
1618 checkPerPackageOk comps not_per_component_reasons
1619 return
1620 [ elaborateSolverToPackage spkg g $
1621 comps ++ maybeToList setupComponent
1623 Left cns ->
1624 dieProgress $
1625 hang
1626 (text "Dependency cycle between the following components:")
1628 (vcat (map (text . componentNameStanza) cns))
1629 where
1630 -- You are eligible to per-component build if this list is empty
1631 why_not_per_component g =
1632 cuz_buildtype ++ cuz_spec ++ cuz_length ++ cuz_flag
1633 where
1634 cuz reason = [text reason]
1635 -- We have to disable per-component for now with
1636 -- Configure-type scripts in order to prevent parallel
1637 -- invocation of the same `./configure` script.
1638 -- See https://github.com/haskell/cabal/issues/4548
1640 -- Moreover, at this point in time, only non-Custom setup scripts
1641 -- are supported. Implementing per-component builds with
1642 -- Custom would require us to create a new 'ElabSetup'
1643 -- type, and teach all of the code paths how to handle it.
1644 -- Once you've implemented this, swap it for the code below.
1645 cuz_buildtype =
1646 case PD.buildType (elabPkgDescription elab0) of
1647 PD.Configure -> cuz "build-type is Configure"
1648 PD.Custom -> cuz "build-type is Custom"
1649 _ -> []
1650 -- cabal-format versions prior to 1.8 have different build-depends semantics
1651 -- for now it's easier to just fallback to legacy-mode when specVersion < 1.8
1652 -- see, https://github.com/haskell/cabal/issues/4121
1653 cuz_spec
1654 | PD.specVersion pd >= CabalSpecV1_8 = []
1655 | otherwise = cuz "cabal-version is less than 1.8"
1656 -- In the odd corner case that a package has no components at all
1657 -- then keep it as a whole package, since otherwise it turns into
1658 -- 0 component graph nodes and effectively vanishes. We want to
1659 -- keep it around at least for error reporting purposes.
1660 cuz_length
1661 | length g > 0 = []
1662 | otherwise = cuz "there are no buildable components"
1663 -- For ease of testing, we let per-component builds be toggled
1664 -- at the top level
1665 cuz_flag
1666 | fromFlagOrDefault True (projectConfigPerComponent sharedPackageConfig) =
1668 | otherwise = cuz "you passed --disable-per-component"
1670 -- \| Sometimes a package may make use of features which are only
1671 -- supported in per-package mode. If this is the case, we should
1672 -- give an error when this occurs.
1673 checkPerPackageOk comps reasons = do
1674 let is_sublib (CLibName (LSubLibName _)) = True
1675 is_sublib _ = False
1676 when (any (matchElabPkg is_sublib) comps) $
1677 dieProgress $
1678 text "Internal libraries only supported with per-component builds."
1679 $$ text "Per-component builds were disabled because"
1680 <+> fsep (punctuate comma reasons)
1681 -- TODO: Maybe exclude Backpack too
1683 elab0 = elaborateSolverToCommon spkg
1684 pkgid = elabPkgSourceId elab0
1685 pd = elabPkgDescription elab0
1687 -- TODO: This is just a skeleton to get elaborateSolverToPackage
1688 -- working correctly
1689 -- TODO: When we actually support building these components, we
1690 -- have to add dependencies on this from all other components
1691 setupComponent :: Maybe ElaboratedConfiguredPackage
1692 setupComponent
1693 | PD.buildType (elabPkgDescription elab0) == PD.Custom =
1694 Just
1695 elab0
1696 { elabModuleShape = emptyModuleShape
1697 , elabUnitId = notImpl "elabUnitId"
1698 , elabComponentId = notImpl "elabComponentId"
1699 , elabLinkedInstantiatedWith = Map.empty
1700 , elabInstallDirs = notImpl "elabInstallDirs"
1701 , elabPkgOrComp = ElabComponent (ElaboratedComponent{..})
1703 | otherwise =
1704 Nothing
1705 where
1706 compSolverName = CD.ComponentSetup
1707 compComponentName = Nothing
1709 dep_pkgs = elaborateLibSolverId mapDep =<< CD.setupDeps deps0
1711 compLibDependencies =
1712 -- MP: No idea what this function does
1713 map (\cid -> (configuredId cid, False)) dep_pkgs
1714 compLinkedLibDependencies = notImpl "compLinkedLibDependencies"
1715 compOrderLibDependencies = notImpl "compOrderLibDependencies"
1717 -- Not supported:
1718 compExeDependencies :: [a]
1719 compExeDependencies = []
1721 compExeDependencyPaths :: [a]
1722 compExeDependencyPaths = []
1724 compPkgConfigDependencies :: [a]
1725 compPkgConfigDependencies = []
1727 notImpl f =
1728 error $
1729 "Distribution.Client.ProjectPlanning.setupComponent: "
1730 ++ f
1731 ++ " not implemented yet"
1733 buildComponent
1734 :: ( ConfiguredComponentMap
1735 , LinkedComponentMap
1736 , Map ComponentId FilePath
1738 -> Cabal.Component
1739 -> LogProgress
1740 ( ( ConfiguredComponentMap
1741 , LinkedComponentMap
1742 , Map ComponentId FilePath
1744 , ElaboratedConfiguredPackage
1746 buildComponent (cc_map, lc_map, exe_map) comp =
1747 addProgressCtx
1748 ( text "In the stanza"
1749 <+> quotes (text (componentNameStanza cname))
1751 $ do
1752 -- 1. Configure the component, but with a place holder ComponentId.
1753 cc0 <-
1754 toConfiguredComponent
1756 (error "Distribution.Client.ProjectPlanning.cc_cid: filled in later")
1757 (Map.unionWith Map.union external_lib_cc_map cc_map)
1758 (Map.unionWith Map.union external_exe_cc_map cc_map)
1759 comp
1761 let do_ cid =
1762 let cid' = annotatedIdToConfiguredId . ci_ann_id $ cid
1763 in (cid', False) -- filled in later in pruneInstallPlanPhase2)
1764 -- 2. Read out the dependencies from the ConfiguredComponent cc0
1765 let compLibDependencies =
1766 -- Nub because includes can show up multiple times
1767 ordNub
1768 ( map
1769 (\cid -> do_ cid)
1770 (cc_includes cc0)
1772 compExeDependencies =
1774 annotatedIdToConfiguredId
1775 (cc_exe_deps cc0)
1776 compExeDependencyPaths =
1777 [ (annotatedIdToConfiguredId aid', path)
1778 | aid' <- cc_exe_deps cc0
1779 , Just paths <- [Map.lookup (ann_id aid') exe_map1]
1780 , path <- paths
1782 elab_comp = ElaboratedComponent{..}
1784 -- 3. Construct a preliminary ElaboratedConfiguredPackage,
1785 -- and use this to compute the component ID. Fix up cc_id
1786 -- correctly.
1787 let elab1 =
1788 elab0
1789 { elabPkgOrComp = ElabComponent $ elab_comp
1791 cid = case elabBuildStyle elab0 of
1792 BuildInplaceOnly{} ->
1793 mkComponentId $
1794 prettyShow pkgid
1795 ++ "-inplace"
1796 ++ ( case Cabal.componentNameString cname of
1797 Nothing -> ""
1798 Just s -> "-" ++ prettyShow s
1800 BuildAndInstall ->
1801 hashedInstalledPackageId
1802 ( packageHashInputs
1803 elaboratedSharedConfig
1804 elab1 -- knot tied
1806 cc = cc0{cc_ann_id = fmap (const cid) (cc_ann_id cc0)}
1807 infoProgress $ dispConfiguredComponent cc
1809 -- 4. Perform mix-in linking
1810 let lookup_uid def_uid =
1811 case Map.lookup (unDefUnitId def_uid) preexistingInstantiatedPkgs of
1812 Just full -> full
1813 Nothing -> error ("lookup_uid: " ++ prettyShow def_uid)
1814 lc <-
1815 toLinkedComponent
1816 verbosity
1817 False
1818 lookup_uid
1819 (elabPkgSourceId elab0)
1820 (Map.union external_lc_map lc_map)
1822 infoProgress $ dispLinkedComponent lc
1823 -- NB: elab is setup to be the correct form for an
1824 -- indefinite library, or a definite library with no holes.
1825 -- We will modify it in 'instantiateInstallPlan' to handle
1826 -- instantiated packages.
1828 -- 5. Construct the final ElaboratedConfiguredPackage
1830 elab2 =
1831 elab1
1832 { elabModuleShape = lc_shape lc
1833 , elabUnitId = abstractUnitId (lc_uid lc)
1834 , elabComponentId = lc_cid lc
1835 , elabLinkedInstantiatedWith = Map.fromList (lc_insts lc)
1836 , elabPkgOrComp =
1837 ElabComponent $
1838 elab_comp
1839 { compLinkedLibDependencies = ordNub (map ci_id (lc_includes lc))
1840 , compOrderLibDependencies =
1841 ordNub
1842 ( map
1843 (abstractUnitId . ci_id)
1844 (lc_includes lc ++ lc_sig_includes lc)
1848 elab =
1849 elab2
1850 { elabInstallDirs =
1851 computeInstallDirs
1852 storeDirLayout
1853 defaultInstallDirs
1854 elaboratedSharedConfig
1855 elab2
1858 -- 6. Construct the updated local maps
1859 let cc_map' = extendConfiguredComponentMap cc cc_map
1860 lc_map' = extendLinkedComponentMap lc lc_map
1861 exe_map' = Map.insert cid (inplace_bin_dir elab) exe_map
1863 return ((cc_map', lc_map', exe_map'), elab)
1864 where
1865 compLinkedLibDependencies = error "buildComponent: compLinkedLibDependencies"
1866 compOrderLibDependencies = error "buildComponent: compOrderLibDependencies"
1868 cname = Cabal.componentName comp
1869 compComponentName = Just cname
1870 compSolverName = CD.componentNameToComponent cname
1872 -- NB: compLinkedLibDependencies and
1873 -- compOrderLibDependencies are defined when we define
1874 -- 'elab'.
1875 external_lib_dep_sids = CD.select (== compSolverName) deps0
1876 external_exe_dep_sids = CD.select (== compSolverName) exe_deps0
1878 external_lib_dep_pkgs = concatMap mapDep external_lib_dep_sids
1880 -- Combine library and build-tool dependencies, for backwards
1881 -- compatibility (See issue #5412 and the documentation for
1882 -- InstallPlan.fromSolverInstallPlan), but prefer the versions
1883 -- specified as build-tools.
1884 external_exe_dep_pkgs =
1885 concatMap mapDep $
1886 ordNubBy (pkgName . packageId) $
1887 external_exe_dep_sids ++ external_lib_dep_sids
1889 external_exe_map =
1890 Map.fromList $
1891 [ (getComponentId pkg, paths)
1892 | pkg <- external_exe_dep_pkgs
1893 , let paths = planPackageExePaths pkg
1895 exe_map1 = Map.union external_exe_map $ fmap (\x -> [x]) exe_map
1897 external_lib_cc_map =
1898 Map.fromListWith Map.union $
1899 map mkCCMapping external_lib_dep_pkgs
1900 external_exe_cc_map =
1901 Map.fromListWith Map.union $
1902 map mkCCMapping external_exe_dep_pkgs
1903 external_lc_map =
1904 Map.fromList $
1905 map mkShapeMapping $
1906 external_lib_dep_pkgs ++ concatMap mapDep external_exe_dep_sids
1908 compPkgConfigDependencies =
1909 [ ( pn
1910 , fromMaybe
1911 ( error $
1912 "compPkgConfigDependencies: impossible! "
1913 ++ prettyShow pn
1914 ++ " from "
1915 ++ prettyShow (elabPkgSourceId elab0)
1917 (pkgConfigDbPkgVersion pkgConfigDB pn)
1919 | PkgconfigDependency pn _ <-
1920 PD.pkgconfigDepends
1921 (Cabal.componentBuildInfo comp)
1924 inplace_bin_dir elab =
1925 binDirectoryFor
1926 distDirLayout
1927 elaboratedSharedConfig
1928 elab
1929 $ case Cabal.componentNameString cname of
1930 Just n -> prettyShow n
1931 Nothing -> ""
1933 -- \| Given a 'SolverId' referencing a dependency on a library, return
1934 -- the 'ElaboratedPlanPackage' corresponding to the library. This
1935 -- returns at most one result.
1936 elaborateLibSolverId
1937 :: (SolverId -> [ElaboratedPlanPackage])
1938 -> SolverId
1939 -> [ElaboratedPlanPackage]
1940 elaborateLibSolverId mapDep = filter (matchPlanPkg (== (CLibName LMainLibName))) . mapDep
1942 -- \| Given an 'ElaboratedPlanPackage', return the paths to where the
1943 -- executables that this package represents would be installed.
1944 -- The only case where multiple paths can be returned is the inplace
1945 -- monolithic package one, since there can be multiple exes and each one
1946 -- has its own directory.
1947 planPackageExePaths :: ElaboratedPlanPackage -> [FilePath]
1948 planPackageExePaths =
1949 -- Pre-existing executables are assumed to be in PATH
1950 -- already. In fact, this should be impossible.
1951 InstallPlan.foldPlanPackage (const []) $ \elab ->
1953 executables :: [FilePath]
1954 executables =
1955 case elabPkgOrComp elab of
1956 -- Monolithic mode: all exes of the package
1957 ElabPackage _ ->
1958 unUnqualComponentName . PD.exeName
1959 <$> PD.executables (elabPkgDescription elab)
1960 -- Per-component mode: just the selected exe
1961 ElabComponent comp ->
1962 case fmap
1963 Cabal.componentNameString
1964 (compComponentName comp) of
1965 Just (Just n) -> [prettyShow n]
1966 _ -> [""]
1968 binDirectoryFor
1969 distDirLayout
1970 elaboratedSharedConfig
1971 elab
1972 <$> executables
1974 elaborateSolverToPackage
1975 :: SolverPackage UnresolvedPkgLoc
1976 -> ComponentsGraph
1977 -> [ElaboratedConfiguredPackage]
1978 -> ElaboratedConfiguredPackage
1979 elaborateSolverToPackage
1980 pkg@( SolverPackage
1981 (SourcePackage pkgid _gpd _srcloc _descOverride)
1982 _flags
1983 _stanzas
1984 _deps0
1985 _exe_deps0
1987 compGraph
1988 comps =
1989 -- Knot tying: the final elab includes the
1990 -- pkgInstalledId, which is calculated by hashing many
1991 -- of the other fields of the elaboratedPackage.
1992 elab
1993 where
1994 elab0@ElaboratedConfiguredPackage{..} =
1995 elaborateSolverToCommon pkg
1997 elab1 =
1998 elab0
1999 { elabUnitId = newSimpleUnitId pkgInstalledId
2000 , elabComponentId = pkgInstalledId
2001 , elabLinkedInstantiatedWith = Map.empty
2002 , elabPkgOrComp = ElabPackage $ ElaboratedPackage{..}
2003 , elabModuleShape = modShape
2006 elab =
2007 elab1
2008 { elabInstallDirs =
2009 computeInstallDirs
2010 storeDirLayout
2011 defaultInstallDirs
2012 elaboratedSharedConfig
2013 elab1
2016 modShape = case find (matchElabPkg (== (CLibName LMainLibName))) comps of
2017 Nothing -> emptyModuleShape
2018 Just e -> Ty.elabModuleShape e
2020 pkgInstalledId
2021 | shouldBuildInplaceOnly pkg =
2022 mkComponentId (prettyShow pkgid ++ "-inplace")
2023 | otherwise =
2024 assert (isJust elabPkgSourceHash) $
2025 hashedInstalledPackageId
2026 ( packageHashInputs
2027 elaboratedSharedConfig
2028 elab -- recursive use of elab
2031 -- Need to filter out internal dependencies, because they don't
2032 -- correspond to anything real anymore.
2033 isExt confid = confSrcId confid /= pkgid
2034 filterExt = filter isExt
2036 filterExt' :: [(ConfiguredId, a)] -> [(ConfiguredId, a)]
2037 filterExt' = filter (isExt . fst)
2039 pkgLibDependencies =
2040 buildComponentDeps (filterExt' . compLibDependencies)
2041 pkgExeDependencies =
2042 buildComponentDeps (filterExt . compExeDependencies)
2043 pkgExeDependencyPaths =
2044 buildComponentDeps (filterExt' . compExeDependencyPaths)
2046 -- TODO: Why is this flat?
2047 pkgPkgConfigDependencies =
2048 CD.flatDeps $ buildComponentDeps compPkgConfigDependencies
2050 pkgDependsOnSelfLib =
2051 CD.fromList
2052 [ (CD.componentNameToComponent cn, [()])
2053 | Graph.N _ cn _ <- fromMaybe [] mb_closure
2055 where
2056 mb_closure = Graph.revClosure compGraph [k | k <- Graph.keys compGraph, is_lib k]
2057 -- NB: the sublib case should not occur, because sub-libraries
2058 -- are not supported without per-component builds
2059 is_lib (CLibName _) = True
2060 is_lib _ = False
2062 buildComponentDeps :: Monoid a => (ElaboratedComponent -> a) -> CD.ComponentDeps a
2063 buildComponentDeps f =
2064 CD.fromList
2065 [ (compSolverName comp, f comp)
2066 | ElaboratedConfiguredPackage{elabPkgOrComp = ElabComponent comp} <- comps
2069 -- NB: This is not the final setting of 'pkgStanzasEnabled'.
2070 -- See [Sticky enabled testsuites]; we may enable some extra
2071 -- stanzas opportunistically when it is cheap to do so.
2073 -- However, we start off by enabling everything that was
2074 -- requested, so that we can maintain an invariant that
2075 -- pkgStanzasEnabled is a superset of elabStanzasRequested
2076 pkgStanzasEnabled = optStanzaKeysFilteredByValue (fromMaybe False) elabStanzasRequested
2078 elaborateSolverToCommon
2079 :: SolverPackage UnresolvedPkgLoc
2080 -> ElaboratedConfiguredPackage
2081 elaborateSolverToCommon
2082 pkg@( SolverPackage
2083 (SourcePackage pkgid gdesc srcloc descOverride)
2084 flags
2085 stanzas
2086 deps0
2087 _exe_deps0
2089 elaboratedPackage
2090 where
2091 elaboratedPackage = ElaboratedConfiguredPackage{..}
2093 -- These get filled in later
2094 elabUnitId = error "elaborateSolverToCommon: elabUnitId"
2095 elabComponentId = error "elaborateSolverToCommon: elabComponentId"
2096 elabInstantiatedWith = Map.empty
2097 elabLinkedInstantiatedWith = error "elaborateSolverToCommon: elabLinkedInstantiatedWith"
2098 elabPkgOrComp = error "elaborateSolverToCommon: elabPkgOrComp"
2099 elabInstallDirs = error "elaborateSolverToCommon: elabInstallDirs"
2100 elabModuleShape = error "elaborateSolverToCommon: elabModuleShape"
2102 elabIsCanonical = True
2103 elabPkgSourceId = pkgid
2104 elabPkgDescription = case PD.finalizePD
2105 flags
2106 elabEnabledSpec
2107 (const True)
2108 platform
2109 (compilerInfo compiler)
2111 gdesc of
2112 Right (desc, _) -> desc
2113 Left _ -> error "Failed to finalizePD in elaborateSolverToCommon"
2114 elabFlagAssignment = flags
2115 elabFlagDefaults =
2116 PD.mkFlagAssignment
2117 [ (PD.flagName flag, PD.flagDefault flag)
2118 | flag <- PD.genPackageFlags gdesc
2121 elabEnabledSpec = enableStanzas stanzas
2122 elabStanzasAvailable = stanzas
2124 elabStanzasRequested :: OptionalStanzaMap (Maybe Bool)
2125 elabStanzasRequested = optStanzaTabulate $ \o -> case o of
2126 -- NB: even if a package stanza is requested, if the package
2127 -- doesn't actually have any of that stanza we omit it from
2128 -- the request, to ensure that we don't decide that this
2129 -- package needs to be rebuilt. (It needs to be done here,
2130 -- because the ElaboratedConfiguredPackage is where we test
2131 -- whether or not there have been changes.)
2132 TestStanzas -> listToMaybe [v | v <- maybeToList tests, _ <- PD.testSuites elabPkgDescription]
2133 BenchStanzas -> listToMaybe [v | v <- maybeToList benchmarks, _ <- PD.benchmarks elabPkgDescription]
2134 where
2135 tests, benchmarks :: Maybe Bool
2136 tests = perPkgOptionMaybe pkgid packageConfigTests
2137 benchmarks = perPkgOptionMaybe pkgid packageConfigBenchmarks
2139 -- This is a placeholder which will get updated by 'pruneInstallPlanPass1'
2140 -- and 'pruneInstallPlanPass2'. We can't populate it here
2141 -- because whether or not tests/benchmarks should be enabled
2142 -- is heuristically calculated based on whether or not the
2143 -- dependencies of the test suite have already been installed,
2144 -- but this function doesn't know what is installed (since
2145 -- we haven't improved the plan yet), so we do it in another pass.
2146 -- Check the comments of those functions for more details.
2147 elabConfigureTargets = []
2148 elabBuildTargets = []
2149 elabTestTargets = []
2150 elabBenchTargets = []
2151 elabReplTarget = []
2152 elabHaddockTargets = []
2154 elabBuildHaddocks =
2155 perPkgOptionFlag pkgid False packageConfigDocumentation
2157 elabPkgSourceLocation = srcloc
2158 elabPkgSourceHash = Map.lookup pkgid sourcePackageHashes
2159 elabLocalToProject = isLocalToProject pkg
2160 elabBuildStyle =
2161 if shouldBuildInplaceOnly pkg
2162 then BuildInplaceOnly OnDisk
2163 else BuildAndInstall
2164 elabPackageDbs = projectConfigPackageDBs sharedPackageConfig
2165 elabBuildPackageDBStack = buildAndRegisterDbs
2166 elabRegisterPackageDBStack = buildAndRegisterDbs
2168 elabSetupScriptStyle = packageSetupScriptStyle elabPkgDescription
2169 elabSetupScriptCliVersion =
2170 packageSetupScriptSpecVersion
2171 elabSetupScriptStyle
2172 elabPkgDescription
2173 libDepGraph
2174 deps0
2175 elabSetupPackageDBStack = buildAndRegisterDbs
2177 elabInplaceBuildPackageDBStack = inplacePackageDbs
2178 elabInplaceRegisterPackageDBStack = inplacePackageDbs
2179 elabInplaceSetupPackageDBStack = inplacePackageDbs
2181 buildAndRegisterDbs
2182 | shouldBuildInplaceOnly pkg = inplacePackageDbs
2183 | otherwise = corePackageDbs
2185 elabPkgDescriptionOverride = descOverride
2187 elabBuildOptions =
2188 LBC.BuildOptions
2189 { withVanillaLib = perPkgOptionFlag pkgid True packageConfigVanillaLib -- TODO: [required feature]: also needs to be handled recursively
2190 , withSharedLib = pkgid `Set.member` pkgsUseSharedLibrary
2191 , withStaticLib = perPkgOptionFlag pkgid False packageConfigStaticLib
2192 , withDynExe = perPkgOptionFlag pkgid False packageConfigDynExe
2193 , withFullyStaticExe = perPkgOptionFlag pkgid False packageConfigFullyStaticExe
2194 , withGHCiLib = perPkgOptionFlag pkgid False packageConfigGHCiLib -- TODO: [required feature] needs to default to enabled on windows still
2195 , withProfExe = perPkgOptionFlag pkgid False packageConfigProf
2196 , withProfLib = pkgid `Set.member` pkgsUseProfilingLibrary
2197 , exeCoverage = perPkgOptionFlag pkgid False packageConfigCoverage
2198 , libCoverage = perPkgOptionFlag pkgid False packageConfigCoverage
2199 , withOptimization = perPkgOptionFlag pkgid NormalOptimisation packageConfigOptimization
2200 , splitObjs = perPkgOptionFlag pkgid False packageConfigSplitObjs
2201 , splitSections = perPkgOptionFlag pkgid False packageConfigSplitSections
2202 , stripLibs = perPkgOptionFlag pkgid False packageConfigStripLibs
2203 , stripExes = perPkgOptionFlag pkgid False packageConfigStripExes
2204 , withDebugInfo = perPkgOptionFlag pkgid NoDebugInfo packageConfigDebugInfo
2205 , relocatable = perPkgOptionFlag pkgid False packageConfigRelocatable
2206 , withProfLibDetail = elabProfExeDetail
2207 , withProfExeDetail = elabProfLibDetail
2210 ( elabProfExeDetail
2211 , elabProfLibDetail
2213 perPkgOptionLibExeFlag
2214 pkgid
2215 ProfDetailDefault
2216 packageConfigProfDetail
2217 packageConfigProfLibDetail
2219 elabDumpBuildInfo = perPkgOptionFlag pkgid NoDumpBuildInfo packageConfigDumpBuildInfo
2221 -- Combine the configured compiler prog settings with the user-supplied
2222 -- config. For the compiler progs any user-supplied config was taken
2223 -- into account earlier when configuring the compiler so its ok that
2224 -- our configured settings for the compiler override the user-supplied
2225 -- config here.
2226 elabProgramPaths =
2227 Map.fromList
2228 [ (programId prog, programPath prog)
2229 | prog <- configuredPrograms compilerprogdb
2231 <> perPkgOptionMapLast pkgid packageConfigProgramPaths
2232 elabProgramArgs =
2233 Map.fromList
2234 [ (programId prog, args)
2235 | prog <- configuredPrograms compilerprogdb
2236 , let args = programOverrideArgs prog
2237 , not (null args)
2239 <> perPkgOptionMapMappend pkgid packageConfigProgramArgs
2240 elabProgramPathExtra = perPkgOptionNubList pkgid packageConfigProgramPathExtra
2241 elabConfigureScriptArgs = perPkgOptionList pkgid packageConfigConfigureArgs
2242 elabExtraLibDirs = perPkgOptionList pkgid packageConfigExtraLibDirs
2243 elabExtraLibDirsStatic = perPkgOptionList pkgid packageConfigExtraLibDirsStatic
2244 elabExtraFrameworkDirs = perPkgOptionList pkgid packageConfigExtraFrameworkDirs
2245 elabExtraIncludeDirs = perPkgOptionList pkgid packageConfigExtraIncludeDirs
2246 elabProgPrefix = perPkgOptionMaybe pkgid packageConfigProgPrefix
2247 elabProgSuffix = perPkgOptionMaybe pkgid packageConfigProgSuffix
2249 elabHaddockHoogle = perPkgOptionFlag pkgid False packageConfigHaddockHoogle
2250 elabHaddockHtml = perPkgOptionFlag pkgid False packageConfigHaddockHtml
2251 elabHaddockHtmlLocation = perPkgOptionMaybe pkgid packageConfigHaddockHtmlLocation
2252 elabHaddockForeignLibs = perPkgOptionFlag pkgid False packageConfigHaddockForeignLibs
2253 elabHaddockForHackage = perPkgOptionFlag pkgid Cabal.ForDevelopment packageConfigHaddockForHackage
2254 elabHaddockExecutables = perPkgOptionFlag pkgid False packageConfigHaddockExecutables
2255 elabHaddockTestSuites = perPkgOptionFlag pkgid False packageConfigHaddockTestSuites
2256 elabHaddockBenchmarks = perPkgOptionFlag pkgid False packageConfigHaddockBenchmarks
2257 elabHaddockInternal = perPkgOptionFlag pkgid False packageConfigHaddockInternal
2258 elabHaddockCss = perPkgOptionMaybe pkgid packageConfigHaddockCss
2259 elabHaddockLinkedSource = perPkgOptionFlag pkgid False packageConfigHaddockLinkedSource
2260 elabHaddockQuickJump = perPkgOptionFlag pkgid False packageConfigHaddockQuickJump
2261 elabHaddockHscolourCss = perPkgOptionMaybe pkgid packageConfigHaddockHscolourCss
2262 elabHaddockContents = perPkgOptionMaybe pkgid packageConfigHaddockContents
2263 elabHaddockIndex = perPkgOptionMaybe pkgid packageConfigHaddockIndex
2264 elabHaddockBaseUrl = perPkgOptionMaybe pkgid packageConfigHaddockBaseUrl
2265 elabHaddockLib = perPkgOptionMaybe pkgid packageConfigHaddockLib
2266 elabHaddockOutputDir = perPkgOptionMaybe pkgid packageConfigHaddockOutputDir
2268 elabTestMachineLog = perPkgOptionMaybe pkgid packageConfigTestMachineLog
2269 elabTestHumanLog = perPkgOptionMaybe pkgid packageConfigTestHumanLog
2270 elabTestShowDetails = perPkgOptionMaybe pkgid packageConfigTestShowDetails
2271 elabTestKeepTix = perPkgOptionFlag pkgid False packageConfigTestKeepTix
2272 elabTestWrapper = perPkgOptionMaybe pkgid packageConfigTestWrapper
2273 elabTestFailWhenNoTestSuites = perPkgOptionFlag pkgid False packageConfigTestFailWhenNoTestSuites
2274 elabTestTestOptions = perPkgOptionList pkgid packageConfigTestTestOptions
2276 elabBenchmarkOptions = perPkgOptionList pkgid packageConfigBenchmarkOptions
2278 perPkgOptionFlag :: PackageId -> a -> (PackageConfig -> Flag a) -> a
2279 perPkgOptionMaybe :: PackageId -> (PackageConfig -> Flag a) -> Maybe a
2280 perPkgOptionList :: PackageId -> (PackageConfig -> [a]) -> [a]
2282 perPkgOptionFlag pkgid def f = fromFlagOrDefault def (lookupPerPkgOption pkgid f)
2283 perPkgOptionMaybe pkgid f = flagToMaybe (lookupPerPkgOption pkgid f)
2284 perPkgOptionList pkgid f = lookupPerPkgOption pkgid f
2285 perPkgOptionNubList pkgid f = fromNubList (lookupPerPkgOption pkgid f)
2286 perPkgOptionMapLast pkgid f = getMapLast (lookupPerPkgOption pkgid f)
2287 perPkgOptionMapMappend pkgid f = getMapMappend (lookupPerPkgOption pkgid f)
2289 perPkgOptionLibExeFlag pkgid def fboth flib = (exe, lib)
2290 where
2291 exe = fromFlagOrDefault def bothflag
2292 lib = fromFlagOrDefault def (bothflag <> libflag)
2294 bothflag = lookupPerPkgOption pkgid fboth
2295 libflag = lookupPerPkgOption pkgid flib
2297 lookupPerPkgOption
2298 :: (Package pkg, Monoid m)
2299 => pkg
2300 -> (PackageConfig -> m)
2301 -> m
2302 lookupPerPkgOption pkg f =
2303 -- This is where we merge the options from the project config that
2304 -- apply to all packages, all project local packages, and to specific
2305 -- named packages
2306 global `mappend` local `mappend` perpkg
2307 where
2308 global = f allPackagesConfig
2309 local
2310 | isLocalToProject pkg =
2311 f localPackagesConfig
2312 | otherwise =
2313 mempty
2314 perpkg = maybe mempty f (Map.lookup (packageName pkg) perPackageConfig)
2316 inplacePackageDbs =
2317 corePackageDbs
2318 ++ [distPackageDB (compilerId compiler)]
2320 corePackageDbs =
2321 applyPackageDbFlags
2322 (storePackageDBStack compiler)
2323 (projectConfigPackageDBs sharedPackageConfig)
2325 -- For this local build policy, every package that lives in a local source
2326 -- dir (as opposed to a tarball), or depends on such a package, will be
2327 -- built inplace into a shared dist dir. Tarball packages that depend on
2328 -- source dir packages will also get unpacked locally.
2329 shouldBuildInplaceOnly :: SolverPackage loc -> Bool
2330 shouldBuildInplaceOnly pkg =
2331 Set.member
2332 (packageId pkg)
2333 pkgsToBuildInplaceOnly
2335 pkgsToBuildInplaceOnly :: Set PackageId
2336 pkgsToBuildInplaceOnly =
2337 Set.fromList $
2338 map packageId $
2339 SolverInstallPlan.reverseDependencyClosure
2340 solverPlan
2341 (map PlannedId (Set.toList pkgsLocalToProject))
2343 isLocalToProject :: Package pkg => pkg -> Bool
2344 isLocalToProject pkg =
2345 Set.member
2346 (packageId pkg)
2347 pkgsLocalToProject
2349 pkgsLocalToProject :: Set PackageId
2350 pkgsLocalToProject =
2351 Set.fromList (catMaybes (map shouldBeLocal localPackages))
2352 -- TODO: localPackages is a misnomer, it's all project packages
2353 -- here is where we decide which ones will be local!
2355 pkgsUseSharedLibrary :: Set PackageId
2356 pkgsUseSharedLibrary =
2357 packagesWithLibDepsDownwardClosedProperty needsSharedLib
2358 where
2359 needsSharedLib pkg =
2360 fromMaybe
2361 compilerShouldUseSharedLibByDefault
2362 (liftM2 (||) pkgSharedLib pkgDynExe)
2363 where
2364 pkgid = packageId pkg
2365 pkgSharedLib = perPkgOptionMaybe pkgid packageConfigSharedLib
2366 pkgDynExe = perPkgOptionMaybe pkgid packageConfigDynExe
2368 -- TODO: [code cleanup] move this into the Cabal lib. It's currently open
2369 -- coded in Distribution.Simple.Configure, but should be made a proper
2370 -- function of the Compiler or CompilerInfo.
2371 compilerShouldUseSharedLibByDefault =
2372 case compilerFlavor compiler of
2373 GHC -> GHC.isDynamic compiler
2374 GHCJS -> GHCJS.isDynamic compiler
2375 _ -> False
2377 pkgsUseProfilingLibrary :: Set PackageId
2378 pkgsUseProfilingLibrary =
2379 packagesWithLibDepsDownwardClosedProperty needsProfilingLib
2380 where
2381 needsProfilingLib pkg =
2382 fromFlagOrDefault False (profBothFlag <> profLibFlag)
2383 where
2384 pkgid = packageId pkg
2385 profBothFlag = lookupPerPkgOption pkgid packageConfigProf
2386 profLibFlag = lookupPerPkgOption pkgid packageConfigProfLib
2387 -- TODO: [code cleanup] unused: the old deprecated packageConfigProfExe
2389 libDepGraph =
2390 Graph.fromDistinctList $
2392 NonSetupLibDepSolverPlanPackage
2393 (SolverInstallPlan.toList solverPlan)
2395 packagesWithLibDepsDownwardClosedProperty property =
2396 Set.fromList
2397 . map packageId
2398 . fromMaybe []
2399 $ Graph.closure
2400 libDepGraph
2401 [ Graph.nodeKey pkg
2402 | pkg <- SolverInstallPlan.toList solverPlan
2403 , property pkg -- just the packages that satisfy the property
2404 -- TODO: [nice to have] this does not check the config consistency,
2405 -- e.g. a package explicitly turning off profiling, but something
2406 -- depending on it that needs profiling. This really needs a separate
2407 -- package config validation/resolution pass.
2410 -- TODO: [nice to have] config consistency checking:
2411 -- + profiling libs & exes, exe needs lib, recursive
2412 -- + shared libs & exes, exe needs lib, recursive
2413 -- + vanilla libs & exes, exe needs lib, recursive
2414 -- + ghci or shared lib needed by TH, recursive, ghc version dependent
2416 -- TODO: Drop matchPlanPkg/matchElabPkg in favor of mkCCMapping
2418 shouldBeLocal :: PackageSpecifier (SourcePackage (PackageLocation loc)) -> Maybe PackageId
2419 shouldBeLocal NamedPackage{} = Nothing
2420 shouldBeLocal (SpecificSourcePackage pkg) = case srcpkgSource pkg of
2421 LocalUnpackedPackage _ -> Just (packageId pkg)
2422 _ -> Nothing
2424 -- | Given a 'ElaboratedPlanPackage', report if it matches a 'ComponentName'.
2425 matchPlanPkg :: (ComponentName -> Bool) -> ElaboratedPlanPackage -> Bool
2426 matchPlanPkg p = InstallPlan.foldPlanPackage (p . ipiComponentName) (matchElabPkg p)
2428 -- | Get the appropriate 'ComponentName' which identifies an installed
2429 -- component.
2430 ipiComponentName :: IPI.InstalledPackageInfo -> ComponentName
2431 ipiComponentName = CLibName . IPI.sourceLibName
2433 -- | Given a 'ElaboratedConfiguredPackage', report if it matches a
2434 -- 'ComponentName'.
2435 matchElabPkg :: (ComponentName -> Bool) -> ElaboratedConfiguredPackage -> Bool
2436 matchElabPkg p elab =
2437 case elabPkgOrComp elab of
2438 ElabComponent comp -> maybe False p (compComponentName comp)
2439 ElabPackage _ ->
2440 -- So, what should we do here? One possibility is to
2441 -- unconditionally return 'True', because whatever it is
2442 -- that we're looking for, it better be in this package.
2443 -- But this is a bit dodgy if the package doesn't actually
2444 -- have, e.g., a library. Fortunately, it's not possible
2445 -- for the build of the library/executables to be toggled
2446 -- by 'pkgStanzasEnabled', so the only thing we have to
2447 -- test is if the component in question is *buildable.*
2449 (p . componentName)
2450 (Cabal.pkgBuildableComponents (elabPkgDescription elab))
2452 -- | Given an 'ElaboratedPlanPackage', generate the mapping from 'PackageName'
2453 -- and 'ComponentName' to the 'ComponentId' that should be used
2454 -- in this case.
2455 mkCCMapping
2456 :: ElaboratedPlanPackage
2457 -> (PackageName, Map ComponentName (AnnotatedId ComponentId))
2458 mkCCMapping =
2459 InstallPlan.foldPlanPackage
2460 ( \ipkg ->
2461 ( packageName ipkg
2462 , Map.singleton
2463 (ipiComponentName ipkg)
2464 -- TODO: libify
2465 ( AnnotatedId
2466 { ann_id = IPI.installedComponentId ipkg
2467 , ann_pid = packageId ipkg
2468 , ann_cname = IPI.sourceComponentName ipkg
2473 $ \elab ->
2474 let mk_aid cn =
2475 AnnotatedId
2476 { ann_id = elabComponentId elab
2477 , ann_pid = packageId elab
2478 , ann_cname = cn
2480 in ( packageName elab
2481 , case elabPkgOrComp elab of
2482 ElabComponent comp ->
2483 case compComponentName comp of
2484 Nothing -> Map.empty
2485 Just n -> Map.singleton n (mk_aid n)
2486 ElabPackage _ ->
2487 Map.fromList $
2489 (\comp -> let cn = Cabal.componentName comp in (cn, mk_aid cn))
2490 (Cabal.pkgBuildableComponents (elabPkgDescription elab))
2493 -- | Given an 'ElaboratedPlanPackage', generate the mapping from 'ComponentId'
2494 -- to the shape of this package, as per mix-in linking.
2495 mkShapeMapping
2496 :: ElaboratedPlanPackage
2497 -> (ComponentId, (OpenUnitId, ModuleShape))
2498 mkShapeMapping dpkg =
2499 (getComponentId dpkg, (indef_uid, shape))
2500 where
2501 (dcid, shape) =
2502 InstallPlan.foldPlanPackage
2503 -- Uses Monad (->)
2504 (liftM2 (,) IPI.installedComponentId shapeInstalledPackage)
2505 (liftM2 (,) elabComponentId elabModuleShape)
2506 dpkg
2507 indef_uid =
2508 IndefFullUnitId
2509 dcid
2510 ( Map.fromList
2511 [ (req, OpenModuleVar req)
2512 | req <- Set.toList (modShapeRequires shape)
2516 -- | Get the bin\/ directories that a package's executables should reside in.
2518 -- The result may be empty if the package does not build any executables.
2520 -- The result may have several entries if this is an inplace build of a package
2521 -- with multiple executables.
2522 binDirectories
2523 :: DistDirLayout
2524 -> ElaboratedSharedConfig
2525 -> ElaboratedConfiguredPackage
2526 -> [FilePath]
2527 binDirectories layout config package = case elabBuildStyle package of
2528 -- quick sanity check: no sense returning a bin directory if we're not going
2529 -- to put any executables in it, that will just clog up the PATH
2530 _ | noExecutables -> []
2531 BuildAndInstall -> [installedBinDirectory package]
2532 BuildInplaceOnly{} -> map (root </>) $ case elabPkgOrComp package of
2533 ElabComponent comp -> case compSolverName comp of
2534 CD.ComponentExe n -> [prettyShow n]
2535 _ -> []
2536 ElabPackage _ ->
2537 map (prettyShow . PD.exeName)
2538 . PD.executables
2539 . elabPkgDescription
2540 $ package
2541 where
2542 noExecutables = null . PD.executables . elabPkgDescription $ package
2543 root =
2544 distBuildDirectory layout (elabDistDirParams config package)
2545 </> "build"
2547 type InstS = Map UnitId ElaboratedPlanPackage
2548 type InstM a = State InstS a
2550 getComponentId
2551 :: ElaboratedPlanPackage
2552 -> ComponentId
2553 getComponentId (InstallPlan.PreExisting dipkg) = IPI.installedComponentId dipkg
2554 getComponentId (InstallPlan.Configured elab) = elabComponentId elab
2555 getComponentId (InstallPlan.Installed elab) = elabComponentId elab
2557 extractElabBuildStyle
2558 :: InstallPlan.GenericPlanPackage ipkg ElaboratedConfiguredPackage
2559 -> BuildStyle
2560 extractElabBuildStyle (InstallPlan.Configured elab) = elabBuildStyle elab
2561 extractElabBuildStyle _ = BuildAndInstall
2563 -- instantiateInstallPlan is responsible for filling out an InstallPlan
2564 -- with all of the extra Configured packages that would be generated by
2565 -- recursively instantiating the dependencies of packages.
2567 -- Suppose we are compiling the following packages:
2569 -- unit f where
2570 -- signature H
2572 -- unit g where
2573 -- dependency f[H=containers:Data.Map]
2575 -- At entry, we have an InstallPlan with a single plan package per
2576 -- actual source package, e.g., only (indefinite!) f and g. The job of
2577 -- instantiation is to turn this into three plan packages: each of the
2578 -- packages as before, but also a new, definite package f[H=containers:Data.Map]
2580 -- How do we do this? The general strategy is to iterate over every
2581 -- package in the existing plan and recursively create new entries for
2582 -- each of its dependencies which is an instantiated package (e.g.,
2583 -- f[H=p:G]). This process must be recursive, as f itself may depend on
2584 -- OTHER packages which it instantiated using its hole H.
2586 -- Some subtleties:
2588 -- * We have to keep track of whether or not we are instantiating with
2589 -- inplace packages, because instantiating a non-inplace package with
2590 -- an inplace packages makes it inplace (since it depends on
2591 -- something in the inplace store)! The rule is that if any of the
2592 -- modules in an instantiation are inplace, then the instantiated
2593 -- unit itself must be inplace. There is then a bunch of faffing
2594 -- about to keep track of BuildStyle.
2596 -- * ElaboratedConfiguredPackage was never really designed for post
2597 -- facto instantiation, so some of the steps for generating new
2598 -- instantiations are a little fraught. For example, the act of
2599 -- flipping a package to be inplace involves faffing about with four
2600 -- fields, because these fields are precomputed. A good refactor
2601 -- would be to reduce the amount of precomputation to simplify the
2602 -- algorithm here.
2604 -- * We use the state monad to cache already instantiated modules, so
2605 -- we don't instantiate the same thing multiple times.
2607 instantiateInstallPlan :: StoreDirLayout -> InstallDirs.InstallDirTemplates -> ElaboratedSharedConfig -> ElaboratedInstallPlan -> ElaboratedInstallPlan
2608 instantiateInstallPlan storeDirLayout defaultInstallDirs elaboratedShared plan =
2609 InstallPlan.new
2610 (IndependentGoals False)
2611 (Graph.fromDistinctList (Map.elems ready_map))
2612 where
2613 pkgs = InstallPlan.toList plan
2615 cmap = Map.fromList [(getComponentId pkg, pkg) | pkg <- pkgs]
2617 instantiateUnitId
2618 :: ComponentId
2619 -> Map ModuleName (Module, BuildStyle)
2620 -> InstM (DefUnitId, BuildStyle)
2621 instantiateUnitId cid insts = state $ \s ->
2622 case Map.lookup uid s of
2623 Nothing ->
2624 -- Knot tied
2625 -- TODO: I don't think the knot tying actually does
2626 -- anything useful
2627 let (r, s') =
2628 runState
2629 (instantiateComponent uid cid insts)
2630 (Map.insert uid r s)
2631 in ((def_uid, extractElabBuildStyle r), Map.insert uid r s')
2632 Just r -> ((def_uid, extractElabBuildStyle r), s)
2633 where
2634 def_uid = mkDefUnitId cid (fmap fst insts)
2635 uid = unDefUnitId def_uid
2637 -- No need to InplaceT; the inplace-ness is properly computed for
2638 -- the ElaboratedPlanPackage, so that will implicitly pass it on
2639 instantiateComponent
2640 :: UnitId
2641 -> ComponentId
2642 -> Map ModuleName (Module, BuildStyle)
2643 -> InstM ElaboratedPlanPackage
2644 instantiateComponent uid cid insts
2645 | Just planpkg <- Map.lookup cid cmap =
2646 case planpkg of
2647 InstallPlan.Configured
2648 ( elab0@ElaboratedConfiguredPackage
2649 { elabPkgOrComp = ElabComponent comp
2651 ) -> do
2652 deps <-
2653 traverse (fmap fst . substUnitId insts) (compLinkedLibDependencies comp)
2654 let build_style = fold (fmap snd insts)
2655 let getDep (Module dep_uid _) = [dep_uid]
2656 elab1 =
2657 fixupBuildStyle build_style $
2658 elab0
2659 { elabUnitId = uid
2660 , elabComponentId = cid
2661 , elabInstantiatedWith = fmap fst insts
2662 , elabIsCanonical = Map.null (fmap fst insts)
2663 , elabPkgOrComp =
2664 ElabComponent
2665 comp
2666 { compOrderLibDependencies =
2667 (if Map.null insts then [] else [newSimpleUnitId cid])
2668 ++ ordNub
2669 ( map
2670 unDefUnitId
2671 (deps ++ concatMap (getDep . fst) (Map.elems insts))
2675 elab =
2676 elab1
2677 { elabInstallDirs =
2678 computeInstallDirs
2679 storeDirLayout
2680 defaultInstallDirs
2681 elaboratedShared
2682 elab1
2684 return $ InstallPlan.Configured elab
2685 _ -> return planpkg
2686 | otherwise = error ("instantiateComponent: " ++ prettyShow cid)
2688 substUnitId :: Map ModuleName (Module, BuildStyle) -> OpenUnitId -> InstM (DefUnitId, BuildStyle)
2689 substUnitId _ (DefiniteUnitId uid) =
2690 -- This COULD actually, secretly, be an inplace package, but in
2691 -- that case it doesn't matter as it's already been recorded
2692 -- in the package that depends on this
2693 return (uid, BuildAndInstall)
2694 substUnitId subst (IndefFullUnitId cid insts) = do
2695 insts' <- substSubst subst insts
2696 instantiateUnitId cid insts'
2698 -- NB: NOT composition
2699 substSubst
2700 :: Map ModuleName (Module, BuildStyle)
2701 -> Map ModuleName OpenModule
2702 -> InstM (Map ModuleName (Module, BuildStyle))
2703 substSubst subst insts = traverse (substModule subst) insts
2705 substModule :: Map ModuleName (Module, BuildStyle) -> OpenModule -> InstM (Module, BuildStyle)
2706 substModule subst (OpenModuleVar mod_name)
2707 | Just m <- Map.lookup mod_name subst = return m
2708 | otherwise = error "substModule: non-closing substitution"
2709 substModule subst (OpenModule uid mod_name) = do
2710 (uid', build_style) <- substUnitId subst uid
2711 return (Module uid' mod_name, build_style)
2713 indefiniteUnitId :: ComponentId -> InstM UnitId
2714 indefiniteUnitId cid = do
2715 let uid = newSimpleUnitId cid
2716 r <- indefiniteComponent uid cid
2717 state $ \s -> (uid, Map.insert uid r s)
2719 indefiniteComponent :: UnitId -> ComponentId -> InstM ElaboratedPlanPackage
2720 indefiniteComponent _uid cid
2721 -- Only need Configured; this phase happens before improvement, so
2722 -- there shouldn't be any Installed packages here.
2723 | Just (InstallPlan.Configured epkg) <- Map.lookup cid cmap
2724 , ElabComponent elab_comp <- elabPkgOrComp epkg =
2726 -- We need to do a little more processing of the includes: some
2727 -- of them are fully definite even without substitution. We
2728 -- want to build those too; see #5634.
2730 -- This code mimics similar code in Distribution.Backpack.ReadyComponent;
2731 -- however, unlike the conversion from LinkedComponent to
2732 -- ReadyComponent, this transformation is done *without*
2733 -- changing the type in question; and what we are simply
2734 -- doing is enforcing tighter invariants on the data
2735 -- structure in question. The new invariant is that there
2736 -- is no IndefFullUnitId in compLinkedLibDependencies that actually
2737 -- has no holes. We couldn't specify this invariant when
2738 -- we initially created the ElaboratedPlanPackage because
2739 -- we have no way of actually reifying the UnitId into a
2740 -- DefiniteUnitId (that's what substUnitId does!)
2741 new_deps <- for (compLinkedLibDependencies elab_comp) $ \uid ->
2742 if Set.null (openUnitIdFreeHoles uid)
2743 then fmap (DefiniteUnitId . fst) (substUnitId Map.empty uid)
2744 else return uid
2745 -- NB: no fixupBuildStyle needed here, as if the indefinite
2746 -- component depends on any inplace packages, it itself must
2747 -- be indefinite! There is no substitution here, we can't
2748 -- post facto add inplace deps
2749 return . InstallPlan.Configured $
2750 epkg
2751 { elabPkgOrComp =
2752 ElabComponent
2753 elab_comp
2754 { compLinkedLibDependencies = new_deps
2755 , -- I think this is right: any new definite unit ids we
2756 -- minted in the phase above need to be built before us.
2757 -- Add 'em in. This doesn't remove any old dependencies
2758 -- on the indefinite package; they're harmless.
2759 compOrderLibDependencies =
2760 ordNub $
2761 compOrderLibDependencies elab_comp
2762 ++ [unDefUnitId d | DefiniteUnitId d <- new_deps]
2765 | Just planpkg <- Map.lookup cid cmap =
2766 return planpkg
2767 | otherwise = error ("indefiniteComponent: " ++ prettyShow cid)
2769 fixupBuildStyle BuildAndInstall elab = elab
2770 fixupBuildStyle _ (elab@ElaboratedConfiguredPackage{elabBuildStyle = BuildInplaceOnly{}}) = elab
2771 fixupBuildStyle t@(BuildInplaceOnly{}) elab =
2772 elab
2773 { elabBuildStyle = t
2774 , elabBuildPackageDBStack = elabInplaceBuildPackageDBStack elab
2775 , elabRegisterPackageDBStack = elabInplaceRegisterPackageDBStack elab
2776 , elabSetupPackageDBStack = elabInplaceSetupPackageDBStack elab
2779 ready_map = execState work Map.empty
2781 work = for_ pkgs $ \pkg ->
2782 case pkg of
2783 InstallPlan.Configured elab
2784 | not (Map.null (elabLinkedInstantiatedWith elab)) ->
2785 indefiniteUnitId (elabComponentId elab)
2786 >> return ()
2787 _ ->
2788 instantiateUnitId (getComponentId pkg) Map.empty
2789 >> return ()
2791 ---------------------------
2792 -- Build targets
2795 -- Refer to ProjectPlanning.Types for details of these important types:
2797 -- data ComponentTarget = ...
2798 -- data SubComponentTarget = ...
2800 -- One step in the build system is to translate higher level intentions like
2801 -- "build this package", "test that package", or "repl that component" into
2802 -- a more detailed specification of exactly which components to build (or other
2803 -- actions like repl or build docs). This translation is somewhat different for
2804 -- different commands. For example "test" for a package will build a different
2805 -- set of components than "build". In addition, the translation of these
2806 -- intentions can fail. For example "run" for a package is only unambiguous
2807 -- when the package has a single executable.
2809 -- So we need a little bit of infrastructure to make it easy for the command
2810 -- implementations to select what component targets are meant when a user asks
2811 -- to do something with a package or component. To do this (and to be able to
2812 -- produce good error messages for mistakes and when targets are not available)
2813 -- we need to gather and summarise accurate information about all the possible
2814 -- targets, both available and unavailable. Then a command implementation can
2815 -- decide which of the available component targets should be selected.
2817 -- | An available target represents a component within a package that a user
2818 -- command could plausibly refer to. In this sense, all the components defined
2819 -- within the package are things the user could refer to, whether or not it
2820 -- would actually be possible to build that component.
2822 -- In particular the available target contains an 'AvailableTargetStatus' which
2823 -- informs us about whether it's actually possible to select this component to
2824 -- be built, and if not why not. This detail makes it possible for command
2825 -- implementations (like @build@, @test@ etc) to accurately report why a target
2826 -- cannot be used.
2828 -- Note that the type parameter is used to help enforce that command
2829 -- implementations can only select targets that can actually be built (by
2830 -- forcing them to return the @k@ value for the selected targets).
2831 -- In particular 'resolveTargets' makes use of this (with @k@ as
2832 -- @('UnitId', ComponentName')@) to identify the targets thus selected.
2833 data AvailableTarget k = AvailableTarget
2834 { availableTargetPackageId :: PackageId
2835 , availableTargetComponentName :: ComponentName
2836 , availableTargetStatus :: AvailableTargetStatus k
2837 , availableTargetLocalToProject :: Bool
2839 deriving (Eq, Show, Functor)
2841 -- | The status of a an 'AvailableTarget' component. This tells us whether
2842 -- it's actually possible to select this component to be built, and if not
2843 -- why not.
2844 data AvailableTargetStatus k
2845 = -- | When the user does @tests: False@
2846 TargetDisabledByUser
2847 | -- | When the solver could not enable tests
2848 TargetDisabledBySolver
2849 | -- | When the component has @buildable: False@
2850 TargetNotBuildable
2851 | -- | When the component is non-core in a non-local package
2852 TargetNotLocal
2853 | -- | The target can or should be built
2854 TargetBuildable k TargetRequested
2855 deriving (Eq, Ord, Show, Functor)
2857 -- | This tells us whether a target ought to be built by default, or only if
2858 -- specifically requested. The policy is that components like libraries and
2859 -- executables are built by default by @build@, but test suites and benchmarks
2860 -- are not, unless this is overridden in the project configuration.
2861 data TargetRequested
2862 = -- | To be built by default
2863 TargetRequestedByDefault
2864 | -- | Not to be built by default
2865 TargetNotRequestedByDefault
2866 deriving (Eq, Ord, Show)
2868 -- | Given the install plan, produce the set of 'AvailableTarget's for each
2869 -- package-component pair.
2871 -- Typically there will only be one such target for each component, but for
2872 -- example if we have a plan with both normal and profiling variants of a
2873 -- component then we would get both as available targets, or similarly if we
2874 -- had a plan that contained two instances of the same version of a package.
2875 -- This approach makes it relatively easy to select all instances\/variants
2876 -- of a component.
2877 availableTargets
2878 :: ElaboratedInstallPlan
2879 -> Map
2880 (PackageId, ComponentName)
2881 [AvailableTarget (UnitId, ComponentName)]
2882 availableTargets installPlan =
2883 let rs =
2884 [ (pkgid, cname, fake, target)
2885 | pkg <- InstallPlan.toList installPlan
2886 , (pkgid, cname, fake, target) <- case pkg of
2887 InstallPlan.PreExisting ipkg -> availableInstalledTargets ipkg
2888 InstallPlan.Installed elab -> availableSourceTargets elab
2889 InstallPlan.Configured elab -> availableSourceTargets elab
2891 in Map.union
2892 ( Map.fromListWith
2893 (++)
2894 [ ((pkgid, cname), [target])
2895 | (pkgid, cname, fake, target) <- rs
2896 , not fake
2899 ( Map.fromList
2900 [ ((pkgid, cname), [target])
2901 | (pkgid, cname, fake, target) <- rs
2902 , fake
2906 -- The normal targets mask the fake ones. We get all instances of the
2907 -- normal ones and only one copy of the fake ones (as there are many
2908 -- duplicates of the fake ones). See 'availableSourceTargets' below for
2909 -- more details on this fake stuff is about.
2911 availableInstalledTargets
2912 :: IPI.InstalledPackageInfo
2913 -> [ ( PackageId
2914 , ComponentName
2915 , Bool
2916 , AvailableTarget (UnitId, ComponentName)
2919 availableInstalledTargets ipkg =
2920 let unitid = installedUnitId ipkg
2921 cname = CLibName LMainLibName
2922 status = TargetBuildable (unitid, cname) TargetRequestedByDefault
2923 target = AvailableTarget (packageId ipkg) cname status False
2924 fake = False
2925 in [(packageId ipkg, cname, fake, target)]
2927 availableSourceTargets
2928 :: ElaboratedConfiguredPackage
2929 -> [ ( PackageId
2930 , ComponentName
2931 , Bool
2932 , AvailableTarget (UnitId, ComponentName)
2935 availableSourceTargets elab =
2936 -- We have a somewhat awkward problem here. We need to know /all/ the
2937 -- components from /all/ the packages because these are the things that
2938 -- users could refer to. Unfortunately, at this stage the elaborated install
2939 -- plan does /not/ contain all components: some components have already
2940 -- been deleted because they cannot possibly be built. This is the case
2941 -- for components that are marked @buildable: False@ in their .cabal files.
2942 -- (It's not unreasonable that the unbuildable components have been pruned
2943 -- as the plan invariant is considerably simpler if all nodes can be built)
2945 -- We can recover the missing components but it's not exactly elegant. For
2946 -- a graph node corresponding to a component we still have the information
2947 -- about the package that it came from, and this includes the names of
2948 -- /all/ the other components in the package. So in principle this lets us
2949 -- find the names of all components, plus full details of the buildable
2950 -- components.
2952 -- Consider for example a package with 3 exe components: foo, bar and baz
2953 -- where foo and bar are buildable, but baz is not. So the plan contains
2954 -- nodes for the components foo and bar. Now we look at each of these two
2955 -- nodes and look at the package they come from and the names of the
2956 -- components in this package. This will give us the names foo, bar and
2957 -- baz, twice (once for each of the two buildable components foo and bar).
2959 -- We refer to these reconstructed missing components as fake targets.
2960 -- It is an invariant that they are not available to be built.
2962 -- To produce the final set of targets we put the fake targets in a finite
2963 -- map (thus eliminating the duplicates) and then we overlay that map with
2964 -- the normal buildable targets. (This is done above in 'availableTargets'.)
2966 [ (packageId elab, cname, fake, target)
2967 | component <- pkgComponents (elabPkgDescription elab)
2968 , let cname = componentName component
2969 status = componentAvailableTargetStatus component
2970 target =
2971 AvailableTarget
2972 { availableTargetPackageId = packageId elab
2973 , availableTargetComponentName = cname
2974 , availableTargetStatus = status
2975 , availableTargetLocalToProject = elabLocalToProject elab
2977 fake = isFakeTarget cname
2978 , -- TODO: The goal of this test is to exclude "instantiated"
2979 -- packages as available targets. This means that you can't
2980 -- ask for a particular instantiated component to be built;
2981 -- it will only get built by a dependency. Perhaps the
2982 -- correct way to implement this is to run selection
2983 -- prior to instantiating packages. If you refactor
2984 -- this, then you can delete this test.
2985 elabIsCanonical elab
2986 , -- Filter out some bogus parts of the cross product that are never needed
2987 case status of
2988 TargetBuildable{} | fake -> False
2989 _ -> True
2991 where
2992 isFakeTarget cname =
2993 case elabPkgOrComp elab of
2994 ElabPackage _ -> False
2995 ElabComponent elabComponent ->
2996 compComponentName elabComponent
2997 /= Just cname
2999 componentAvailableTargetStatus
3000 :: Component -> AvailableTargetStatus (UnitId, ComponentName)
3001 componentAvailableTargetStatus component =
3002 case componentOptionalStanza $ CD.componentNameToComponent cname of
3003 -- it is not an optional stanza, so a library, exe or foreign lib
3004 Nothing
3005 | not buildable -> TargetNotBuildable
3006 | otherwise ->
3007 TargetBuildable
3008 (elabUnitId elab, cname)
3009 TargetRequestedByDefault
3010 -- it is not an optional stanza, so a testsuite or benchmark
3011 Just stanza ->
3012 case ( optStanzaLookup stanza (elabStanzasRequested elab) -- TODO
3013 , optStanzaSetMember stanza (elabStanzasAvailable elab)
3014 ) of
3015 _ | not withinPlan -> TargetNotLocal
3016 (Just False, _) -> TargetDisabledByUser
3017 (Nothing, False) -> TargetDisabledBySolver
3018 _ | not buildable -> TargetNotBuildable
3019 (Just True, True) ->
3020 TargetBuildable
3021 (elabUnitId elab, cname)
3022 TargetRequestedByDefault
3023 (Nothing, True) ->
3024 TargetBuildable
3025 (elabUnitId elab, cname)
3026 TargetNotRequestedByDefault
3027 (Just True, False) ->
3028 error $ "componentAvailableTargetStatus: impossible; cname=" ++ prettyShow cname
3029 where
3030 cname = componentName component
3031 buildable = PD.buildable (componentBuildInfo component)
3032 withinPlan =
3033 elabLocalToProject elab
3034 || case elabPkgOrComp elab of
3035 ElabComponent elabComponent ->
3036 compComponentName elabComponent == Just cname
3037 ElabPackage _ ->
3038 case componentName component of
3039 CLibName (LMainLibName) -> True
3040 CExeName _ -> True
3041 -- TODO: what about sub-libs and foreign libs?
3042 _ -> False
3044 -- | Merge component targets that overlap each other. Specially when we have
3045 -- multiple targets for the same component and one of them refers to the whole
3046 -- component (rather than a module or file within) then all the other targets
3047 -- for that component are subsumed.
3049 -- We also allow for information associated with each component target, and
3050 -- whenever we targets subsume each other we aggregate their associated info.
3051 nubComponentTargets :: [(ComponentTarget, a)] -> [(ComponentTarget, NonEmpty a)]
3052 nubComponentTargets =
3053 concatMap (wholeComponentOverrides . map snd)
3054 . groupBy ((==) `on` fst)
3055 . sortBy (compare `on` fst)
3056 . map (\t@((ComponentTarget cname _, _)) -> (cname, t))
3057 . map compatSubComponentTargets
3058 where
3059 -- If we're building the whole component then that the only target all we
3060 -- need, otherwise we can have several targets within the component.
3061 wholeComponentOverrides
3062 :: [(ComponentTarget, a)]
3063 -> [(ComponentTarget, NonEmpty a)]
3064 wholeComponentOverrides ts =
3065 case [ta | ta@(ComponentTarget _ WholeComponent, _) <- ts] of
3066 ((t, x) : _) ->
3068 -- Delete tuple (t, x) from original list to avoid duplicates.
3069 -- Use 'deleteBy', to avoid additional Class constraint on 'nubComponentTargets'.
3070 ts' = deleteBy (\(t1, _) (t2, _) -> t1 == t2) (t, x) ts
3072 [(t, x :| map snd ts')]
3073 [] -> [(t, x :| []) | (t, x) <- ts]
3075 -- Not all Cabal Setup.hs versions support sub-component targets, so switch
3076 -- them over to the whole component
3077 compatSubComponentTargets :: (ComponentTarget, a) -> (ComponentTarget, a)
3078 compatSubComponentTargets target@(ComponentTarget cname _subtarget, x)
3079 | not setupHsSupportsSubComponentTargets =
3080 (ComponentTarget cname WholeComponent, x)
3081 | otherwise = target
3083 -- Actually the reality is that no current version of Cabal's Setup.hs
3084 -- build command actually support building specific files or modules.
3085 setupHsSupportsSubComponentTargets = False
3087 -- TODO: when that changes, adjust this test, e.g.
3088 -- \| pkgSetupScriptCliVersion >= Version [x,y] []
3090 pkgHasEphemeralBuildTargets :: ElaboratedConfiguredPackage -> Bool
3091 pkgHasEphemeralBuildTargets elab =
3092 (not . null) (elabReplTarget elab)
3093 || (not . null) (elabTestTargets elab)
3094 || (not . null) (elabBenchTargets elab)
3095 || (not . null) (elabHaddockTargets elab)
3096 || (not . null)
3097 [ () | ComponentTarget _ subtarget <- elabBuildTargets elab, subtarget /= WholeComponent
3100 -- | The components that we'll build all of, meaning that after they're built
3101 -- we can skip building them again (unlike with building just some modules or
3102 -- other files within a component).
3103 elabBuildTargetWholeComponents
3104 :: ElaboratedConfiguredPackage
3105 -> Set ComponentName
3106 elabBuildTargetWholeComponents elab =
3107 Set.fromList
3108 [cname | ComponentTarget cname WholeComponent <- elabBuildTargets elab]
3110 ------------------------------------------------------------------------------
3112 -- * Install plan pruning
3114 ------------------------------------------------------------------------------
3116 -- | How 'pruneInstallPlanToTargets' should interpret the per-package
3117 -- 'ComponentTarget's: as build, repl or haddock targets.
3118 data TargetAction
3119 = TargetActionConfigure
3120 | TargetActionBuild
3121 | TargetActionRepl
3122 | TargetActionTest
3123 | TargetActionBench
3124 | TargetActionHaddock
3126 -- | Given a set of per-package\/per-component targets, take the subset of the
3127 -- install plan needed to build those targets. Also, update the package config
3128 -- to specify which optional stanzas to enable, and which targets within each
3129 -- package to build.
3131 -- NB: Pruning happens after improvement, which is important because we
3132 -- will prune differently depending on what is already installed (to
3133 -- implement "sticky" test suite enabling behavior).
3134 pruneInstallPlanToTargets
3135 :: TargetAction
3136 -> Map UnitId [ComponentTarget]
3137 -> ElaboratedInstallPlan
3138 -> ElaboratedInstallPlan
3139 pruneInstallPlanToTargets targetActionType perPkgTargetsMap elaboratedPlan =
3140 InstallPlan.new (InstallPlan.planIndepGoals elaboratedPlan)
3141 . Graph.fromDistinctList
3142 -- We have to do the pruning in two passes
3143 . pruneInstallPlanPass2
3144 . pruneInstallPlanPass1
3145 -- Set the targets that will be the roots for pruning
3146 . setRootTargets targetActionType perPkgTargetsMap
3147 . InstallPlan.toList
3148 $ elaboratedPlan
3150 -- | This is a temporary data type, where we temporarily
3151 -- override the graph dependencies of an 'ElaboratedPackage',
3152 -- so we can take a closure over them. We'll throw out the
3153 -- overridden dependencies when we're done so it's strictly temporary.
3155 -- For 'ElaboratedComponent', this the cached unit IDs always
3156 -- coincide with the real thing.
3157 data PrunedPackage = PrunedPackage ElaboratedConfiguredPackage [UnitId]
3159 instance Package PrunedPackage where
3160 packageId (PrunedPackage elab _) = packageId elab
3162 instance HasUnitId PrunedPackage where
3163 installedUnitId = Graph.nodeKey
3165 instance Graph.IsNode PrunedPackage where
3166 type Key PrunedPackage = UnitId
3167 nodeKey (PrunedPackage elab _) = Graph.nodeKey elab
3168 nodeNeighbors (PrunedPackage _ deps) = deps
3170 fromPrunedPackage :: PrunedPackage -> ElaboratedConfiguredPackage
3171 fromPrunedPackage (PrunedPackage elab _) = elab
3173 -- | Set the build targets based on the user targets (but not rev deps yet).
3174 -- This is required before we can prune anything.
3175 setRootTargets
3176 :: TargetAction
3177 -> Map UnitId [ComponentTarget]
3178 -> [ElaboratedPlanPackage]
3179 -> [ElaboratedPlanPackage]
3180 setRootTargets targetAction perPkgTargetsMap =
3181 assert (not (Map.null perPkgTargetsMap)) $
3182 assert (all (not . null) (Map.elems perPkgTargetsMap)) $
3183 map (mapConfiguredPackage setElabBuildTargets)
3184 where
3185 -- Set the targets we'll build for this package/component. This is just
3186 -- based on the root targets from the user, not targets implied by reverse
3187 -- dependencies. Those comes in the second pass once we know the rev deps.
3189 setElabBuildTargets elab =
3190 case ( Map.lookup (installedUnitId elab) perPkgTargetsMap
3191 , targetAction
3192 ) of
3193 (Nothing, _) -> elab
3194 (Just tgts, TargetActionConfigure) -> elab{elabConfigureTargets = tgts}
3195 (Just tgts, TargetActionBuild) -> elab{elabBuildTargets = tgts}
3196 (Just tgts, TargetActionTest) -> elab{elabTestTargets = tgts}
3197 (Just tgts, TargetActionBench) -> elab{elabBenchTargets = tgts}
3198 (Just tgts, TargetActionRepl) ->
3199 elab
3200 { elabReplTarget = tgts
3201 , elabBuildHaddocks = False
3202 , elabBuildStyle = BuildInplaceOnly InMemory
3204 (Just tgts, TargetActionHaddock) ->
3205 foldr
3206 setElabHaddockTargets
3207 ( elab
3208 { elabHaddockTargets = tgts
3209 , elabBuildHaddocks = True
3212 tgts
3214 setElabHaddockTargets tgt elab
3215 | isTestComponentTarget tgt = elab{elabHaddockTestSuites = True}
3216 | isBenchComponentTarget tgt = elab{elabHaddockBenchmarks = True}
3217 | isForeignLibComponentTarget tgt = elab{elabHaddockForeignLibs = True}
3218 | isExeComponentTarget tgt = elab{elabHaddockExecutables = True}
3219 | isSubLibComponentTarget tgt = elab{elabHaddockInternal = True}
3220 | otherwise = elab
3222 minVersionReplFlagFile :: Version
3223 minVersionReplFlagFile = mkVersion [3, 9]
3225 -- | Assuming we have previously set the root build targets (i.e. the user
3226 -- targets but not rev deps yet), the first pruning pass does two things:
3228 -- * A first go at determining which optional stanzas (testsuites, benchmarks)
3229 -- are needed. We have a second go in the next pass.
3230 -- * Take the dependency closure using pruned dependencies. We prune deps that
3231 -- are used only by unneeded optional stanzas. These pruned deps are only
3232 -- used for the dependency closure and are not persisted in this pass.
3233 pruneInstallPlanPass1
3234 :: [ElaboratedPlanPackage]
3235 -> [ElaboratedPlanPackage]
3236 pruneInstallPlanPass1 pkgs
3237 -- if there are repl targets, we need to do a bit more work
3238 -- See Note [Pruning for Multi Repl]
3239 | anyReplTarget = final_final_graph
3240 -- otherwise we'll do less
3241 | otherwise = pruned_packages
3242 where
3243 pkgs' :: [InstallPlan.GenericPlanPackage IPI.InstalledPackageInfo PrunedPackage]
3244 pkgs' = map (mapConfiguredPackage prune) pkgs
3246 prune :: ElaboratedConfiguredPackage -> PrunedPackage
3247 prune elab = PrunedPackage elab' (pruneOptionalDependencies elab')
3248 where
3249 elab' = addOptionalStanzas elab
3251 graph = Graph.fromDistinctList pkgs'
3253 roots :: [UnitId]
3254 roots = mapMaybe find_root pkgs'
3256 -- Make a closed graph by calculating the closure from the roots
3257 pruned_packages :: [ElaboratedPlanPackage]
3258 pruned_packages = map (mapConfiguredPackage fromPrunedPackage) (fromMaybe [] $ Graph.closure graph roots)
3260 closed_graph :: Graph.Graph ElaboratedPlanPackage
3261 closed_graph = Graph.fromDistinctList pruned_packages
3263 -- whether any package has repl targets enabled.
3264 anyReplTarget :: Bool
3265 anyReplTarget = any is_repl_gpp pkgs'
3266 where
3267 is_repl_gpp (InstallPlan.Configured pkg) = is_repl_pp pkg
3268 is_repl_gpp _ = False
3270 is_repl_pp (PrunedPackage elab _) = not (null (elabReplTarget elab))
3272 -- Anything which is inplace and left after pruning could be a repl target, then just need to check the
3273 -- reverse closure after calculating roots to capture dependencies which are on the path between roots.
3274 -- In order to start a multi-repl session with all the desired targets we need to load all these components into
3275 -- the repl at once to satisfy the closure property.
3276 all_desired_repl_targets = Set.fromList [elabUnitId cp | InstallPlan.Configured cp <- fromMaybe [] $ Graph.revClosure closed_graph roots]
3278 add_repl_target :: ElaboratedConfiguredPackage -> ElaboratedConfiguredPackage
3279 add_repl_target ecp
3280 | elabUnitId ecp `Set.member` all_desired_repl_targets =
3282 { elabReplTarget = maybeToList (ComponentTarget <$> (elabComponentName ecp) <*> pure WholeComponent)
3283 , elabBuildStyle = BuildInplaceOnly InMemory
3285 | otherwise = ecp
3287 -- Add the repl target information to the ElaboratedPlanPackages
3288 graph_with_repl_targets
3289 | anyReplTarget = map (mapConfiguredPackage add_repl_target) (Graph.toList closed_graph)
3290 | otherwise = Graph.toList closed_graph
3292 -- But check that all the InMemory targets have a new enough version of Cabal,
3293 -- otherwise we will confuse Setup.hs by passing new arguments which it doesn't understand
3294 -- later down the line. We try to remove just these edges, if it doesn't break the overall structure
3295 -- then we just report to the user that their target will not be loaded for this reason.
3297 -- 'bad' are the nodes with a too old version of Cabal
3298 -- 'good' are the nodes with a new-enough version of Cabal
3299 (bad, _good) = partitionEithers (map go graph_with_repl_targets)
3300 where
3301 go :: ElaboratedPlanPackage -> Either UnitId ElaboratedPlanPackage
3302 go (InstallPlan.Configured cp)
3303 | BuildInplaceOnly InMemory <- elabBuildStyle cp
3304 , elabSetupScriptCliVersion cp < minVersionReplFlagFile =
3305 Left (elabUnitId cp)
3306 go (InstallPlan.Configured c) = Right (InstallPlan.Configured c)
3307 go c = Right c
3309 -- Now take the upwards closure from the bad nodes, and find the other `BuildInplaceOnly InMemory` packages that clobbers,
3310 -- disables those and issue a warning to the user. Because we aren't going to be able to load those into memory as well
3311 -- because the thing it depends on is not going to be in memory.
3312 disabled_repl_targets =
3313 [ c | InstallPlan.Configured c <- fromMaybe [] $ Graph.revClosure (Graph.fromDistinctList graph_with_repl_targets) bad, BuildInplaceOnly InMemory <- [elabBuildStyle c]
3316 remove_repl_target :: ElaboratedConfiguredPackage -> ElaboratedConfiguredPackage
3317 remove_repl_target ecp
3318 | ecp `elem` disabled_repl_targets =
3320 { elabReplTarget = []
3321 , elabBuildStyle = BuildInplaceOnly OnDisk
3323 | otherwise = ecp
3325 final_graph_with_repl_targets = map (mapConfiguredPackage remove_repl_target) graph_with_repl_targets
3327 -- Now find what the new roots are after we have disabled things which we can't build (and the things above that)
3328 new_roots :: [UnitId]
3329 new_roots = mapMaybe find_root (map (mapConfiguredPackage prune) final_graph_with_repl_targets)
3331 -- Then take the final closure from these new roots to remove these things
3332 -- TODO: Can probably just remove them directly in remove_repl_target.
3333 final_final_graph = fromMaybe [] $ Graph.closure (Graph.fromDistinctList final_graph_with_repl_targets) new_roots
3335 is_root :: PrunedPackage -> Maybe UnitId
3336 is_root (PrunedPackage elab _) =
3337 if not $
3339 [ null (elabConfigureTargets elab)
3340 , null (elabBuildTargets elab)
3341 , null (elabTestTargets elab)
3342 , null (elabBenchTargets elab)
3343 , null (elabReplTarget elab)
3344 , null (elabHaddockTargets elab)
3346 then Just (installedUnitId elab)
3347 else Nothing
3349 find_root (InstallPlan.Configured pkg) = is_root pkg
3350 -- When using the extra-packages stanza we need to
3351 -- look at installed packages as well.
3352 find_root (InstallPlan.Installed pkg) = is_root pkg
3353 find_root _ = Nothing
3355 -- Note [Sticky enabled testsuites]
3356 -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
3357 -- The testsuite and benchmark targets are somewhat special in that we need
3358 -- to configure the packages with them enabled, and we need to do that even
3359 -- if we only want to build one of several testsuites.
3361 -- There are two cases in which we will enable the testsuites (or
3362 -- benchmarks): if one of the targets is a testsuite, or if all of the
3363 -- testsuite dependencies are already cached in the store. The rationale
3364 -- for the latter is to minimise how often we have to reconfigure due to
3365 -- the particular targets we choose to build. Otherwise choosing to build
3366 -- a testsuite target, and then later choosing to build an exe target
3367 -- would involve unnecessarily reconfiguring the package with testsuites
3368 -- disabled. Technically this introduces a little bit of stateful
3369 -- behaviour to make this "sticky", but it should be benign.
3371 -- Decide whether or not to enable testsuites and benchmarks.
3372 -- See [Sticky enabled testsuites]
3373 addOptionalStanzas :: ElaboratedConfiguredPackage -> ElaboratedConfiguredPackage
3374 addOptionalStanzas elab@ElaboratedConfiguredPackage{elabPkgOrComp = ElabPackage pkg} =
3375 elab
3376 { elabPkgOrComp = ElabPackage (pkg{pkgStanzasEnabled = stanzas})
3378 where
3379 stanzas :: OptionalStanzaSet
3380 -- By default, we enabled all stanzas requested by the user,
3381 -- as per elabStanzasRequested, done in
3382 -- 'elaborateSolverToPackage'
3383 stanzas =
3384 pkgStanzasEnabled pkg
3385 -- optionalStanzasRequiredByTargets has to be done at
3386 -- prune-time because it depends on 'elabTestTargets'
3387 -- et al, which is done by 'setRootTargets' at the
3388 -- beginning of pruning.
3389 <> optionalStanzasRequiredByTargets elab
3390 -- optionalStanzasWithDepsAvailable has to be done at
3391 -- prune-time because it depends on what packages are
3392 -- installed, which is not known until after improvement
3393 -- (pruning is done after improvement)
3394 <> optionalStanzasWithDepsAvailable availablePkgs elab pkg
3395 addOptionalStanzas elab = elab
3397 -- Calculate package dependencies but cut out those needed only by
3398 -- optional stanzas that we've determined we will not enable.
3399 -- These pruned deps are not persisted in this pass since they're based on
3400 -- the optional stanzas and we'll make further tweaks to the optional
3401 -- stanzas in the next pass.
3403 pruneOptionalDependencies :: ElaboratedConfiguredPackage -> [UnitId]
3404 pruneOptionalDependencies elab@ElaboratedConfiguredPackage{elabPkgOrComp = ElabComponent _} =
3405 InstallPlan.depends elab -- no pruning
3406 pruneOptionalDependencies ElaboratedConfiguredPackage{elabPkgOrComp = ElabPackage pkg} =
3407 (CD.flatDeps . CD.filterDeps keepNeeded) (pkgOrderDependencies pkg)
3408 where
3409 keepNeeded (CD.ComponentTest _) _ = TestStanzas `optStanzaSetMember` stanzas
3410 keepNeeded (CD.ComponentBench _) _ = BenchStanzas `optStanzaSetMember` stanzas
3411 keepNeeded _ _ = True
3412 stanzas = pkgStanzasEnabled pkg
3414 optionalStanzasRequiredByTargets
3415 :: ElaboratedConfiguredPackage
3416 -> OptionalStanzaSet
3417 optionalStanzasRequiredByTargets pkg =
3418 optStanzaSetFromList
3419 [ stanza
3420 | ComponentTarget cname _ <-
3421 elabBuildTargets pkg
3422 ++ elabTestTargets pkg
3423 ++ elabBenchTargets pkg
3424 ++ elabReplTarget pkg
3425 ++ elabHaddockTargets pkg
3426 , stanza <-
3427 maybeToList $
3428 componentOptionalStanza $
3429 CD.componentNameToComponent cname
3432 availablePkgs =
3433 Set.fromList
3434 [ installedUnitId pkg
3435 | InstallPlan.PreExisting pkg <- pkgs
3439 Note [Pruning for Multi Repl]
3440 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
3442 For a multi-repl session, where we load more than one component into a GHCi repl,
3443 it is required to uphold the so-called *closure property*.
3444 This property, whose exact Note you can read in the GHC codebase, states
3445 roughly:
3447 \* If a component you want to load into a repl session transitively depends on a
3448 component which transitively depends on another component you want to
3449 load into the repl, then this component needs to be loaded
3450 into the repl session as well.
3452 We make sure here, that this property is upheld, by calculating the
3453 graph of components that we need to load into the repl given the set of 'roots' which
3454 are the targets specified by the user.
3456 Practically, this is simply achieved by traversing all dependencies of
3457 our roots (graph closure), and then from this closed graph, we calculate
3458 the reverse closure, which gives us all components that depend on
3459 'roots'. Thus, the result is a list of components that we need to load
3460 into the repl to uphold the closure property.
3462 Further to this, we then check that all the enabled components are using a new enough
3463 version of Cabal which understands the repl option to write the arguments to a file.
3465 If there is a package using a custom Setup.hs which is linked against a too old version
3466 of Cabal then we need to disable that as otherwise we will end up passing unknown
3467 arguments to `./Setup`.
3470 -- | Given a set of already installed packages @availablePkgs@,
3471 -- determine the set of available optional stanzas from @pkg@
3472 -- which have all of their dependencies already installed. This is used
3473 -- to implement "sticky" testsuites, where once we have installed
3474 -- all of the deps needed for the test suite, we go ahead and
3475 -- enable it always.
3476 optionalStanzasWithDepsAvailable
3477 :: Set UnitId
3478 -> ElaboratedConfiguredPackage
3479 -> ElaboratedPackage
3480 -> OptionalStanzaSet
3481 optionalStanzasWithDepsAvailable availablePkgs elab pkg =
3482 optStanzaSetFromList
3483 [ stanza
3484 | stanza <- optStanzaSetToList (elabStanzasAvailable elab)
3485 , let deps :: [UnitId]
3486 deps =
3487 CD.select
3488 (optionalStanzaDeps stanza)
3489 -- TODO: probably need to select other
3490 -- dep types too eventually
3491 (pkgOrderDependencies pkg)
3492 , all (`Set.member` availablePkgs) deps
3494 where
3495 optionalStanzaDeps TestStanzas (CD.ComponentTest _) = True
3496 optionalStanzaDeps BenchStanzas (CD.ComponentBench _) = True
3497 optionalStanzaDeps _ _ = False
3499 -- The second pass does three things:
3502 -- * A second go at deciding which optional stanzas to enable.
3504 -- * Prune the dependencies based on the final choice of optional stanzas.
3506 -- * Extend the targets within each package to build, now we know the reverse
3508 -- dependencies, ie we know which libs are needed as deps by other packages.
3510 -- Achieving sticky behaviour with enabling\/disabling optional stanzas is
3511 -- tricky. The first approximation was handled by the first pass above, but
3512 -- it's not quite enough. That pass will enable stanzas if all of the deps
3513 -- of the optional stanza are already installed /in the store/. That's important
3514 -- but it does not account for dependencies that get built inplace as part of
3515 -- the project. We cannot take those inplace build deps into account in the
3516 -- pruning pass however because we don't yet know which ones we're going to
3517 -- build. Once we do know, we can have another go and enable stanzas that have
3518 -- all their deps available. Now we can consider all packages in the pruned
3519 -- plan to be available, including ones we already decided to build from
3520 -- source.
3522 -- Deciding which targets to build depends on knowing which packages have
3523 -- reverse dependencies (ie are needed). This requires the result of first
3524 -- pass, which is another reason we have to split it into two passes.
3526 -- Note that just because we might enable testsuites or benchmarks (in the
3527 -- first or second pass) doesn't mean that we build all (or even any) of them.
3528 -- That depends on which targets we picked in the first pass.
3530 pruneInstallPlanPass2
3531 :: [ElaboratedPlanPackage]
3532 -> [ElaboratedPlanPackage]
3533 pruneInstallPlanPass2 pkgs =
3534 map (mapConfiguredPackage setStanzasDepsAndTargets) pkgs
3535 where
3536 setStanzasDepsAndTargets elab =
3537 elab
3538 { elabBuildTargets =
3539 ordNub $
3540 elabBuildTargets elab
3541 ++ libTargetsRequiredForRevDeps
3542 ++ exeTargetsRequiredForRevDeps
3543 , elabPkgOrComp =
3544 case elabPkgOrComp elab of
3545 ElabPackage pkg ->
3546 let stanzas =
3547 pkgStanzasEnabled pkg
3548 <> optionalStanzasWithDepsAvailable availablePkgs elab pkg
3550 keepNeeded :: CD.Component -> a -> Bool
3551 keepNeeded (CD.ComponentTest _) _ = TestStanzas `optStanzaSetMember` stanzas
3552 keepNeeded (CD.ComponentBench _) _ = BenchStanzas `optStanzaSetMember` stanzas
3553 keepNeeded _ _ = True
3554 in ElabPackage $
3556 { pkgStanzasEnabled =
3557 stanzas
3558 , pkgLibDependencies =
3559 CD.mapDeps (\_ -> map addInternal) $
3560 CD.filterDeps keepNeeded (pkgLibDependencies pkg)
3561 , pkgExeDependencies =
3562 CD.filterDeps keepNeeded (pkgExeDependencies pkg)
3563 , pkgExeDependencyPaths =
3564 CD.filterDeps keepNeeded (pkgExeDependencyPaths pkg)
3566 ElabComponent comp ->
3567 ElabComponent $
3568 comp
3569 { compLibDependencies = map addInternal (compLibDependencies comp)
3572 where
3573 -- We initially assume that all the dependencies are external (hence the boolean is always
3574 -- False) and here we correct the dependencies so the right packages are marked promised.
3575 addInternal (cid, _) = (cid, (cid `Set.member` inMemoryTargets))
3577 libTargetsRequiredForRevDeps =
3579 | installedUnitId elab `Set.member` hasReverseLibDeps
3580 , let c = ComponentTarget (CLibName Cabal.defaultLibName) WholeComponent
3581 , -- Don't enable building for anything which is being build in memory
3582 elabBuildStyle elab /= BuildInplaceOnly InMemory
3584 exeTargetsRequiredForRevDeps =
3585 -- TODO: allow requesting executable with different name
3586 -- than package name
3587 [ ComponentTarget
3588 ( Cabal.CExeName $
3589 packageNameToUnqualComponentName $
3590 packageName $
3591 elabPkgSourceId elab
3593 WholeComponent
3594 | installedUnitId elab `Set.member` hasReverseExeDeps
3597 availablePkgs :: Set UnitId
3598 availablePkgs = Set.fromList (map installedUnitId pkgs)
3600 inMemoryTargets :: Set ConfiguredId
3601 inMemoryTargets = do
3602 Set.fromList
3603 [ configuredId pkg
3604 | InstallPlan.Configured pkg <- pkgs
3605 , BuildInplaceOnly InMemory <- [elabBuildStyle pkg]
3608 hasReverseLibDeps :: Set UnitId
3609 hasReverseLibDeps =
3610 Set.fromList
3611 [ depid
3612 | InstallPlan.Configured pkg <- pkgs
3613 , depid <- elabOrderLibDependencies pkg
3616 hasReverseExeDeps :: Set UnitId
3617 hasReverseExeDeps =
3618 Set.fromList
3619 [ depid
3620 | InstallPlan.Configured pkg <- pkgs
3621 , depid <- elabOrderExeDependencies pkg
3624 mapConfiguredPackage
3625 :: (srcpkg -> srcpkg')
3626 -> InstallPlan.GenericPlanPackage ipkg srcpkg
3627 -> InstallPlan.GenericPlanPackage ipkg srcpkg'
3628 mapConfiguredPackage f (InstallPlan.Configured pkg) =
3629 InstallPlan.Configured (f pkg)
3630 mapConfiguredPackage f (InstallPlan.Installed pkg) =
3631 InstallPlan.Installed (f pkg)
3632 mapConfiguredPackage _ (InstallPlan.PreExisting pkg) =
3633 InstallPlan.PreExisting pkg
3635 ------------------------------------
3636 -- Support for --only-dependencies
3639 -- | Try to remove the given targets from the install plan.
3641 -- This is not always possible.
3642 pruneInstallPlanToDependencies
3643 :: Set UnitId
3644 -> ElaboratedInstallPlan
3645 -> Either
3646 CannotPruneDependencies
3647 ElaboratedInstallPlan
3648 pruneInstallPlanToDependencies pkgTargets installPlan =
3649 assert
3650 ( all
3651 (isJust . InstallPlan.lookup installPlan)
3652 (Set.toList pkgTargets)
3654 $ fmap (InstallPlan.new (InstallPlan.planIndepGoals installPlan))
3655 . checkBrokenDeps
3656 . Graph.fromDistinctList
3657 . filter (\pkg -> installedUnitId pkg `Set.notMember` pkgTargets)
3658 . InstallPlan.toList
3659 $ installPlan
3660 where
3661 -- Our strategy is to remove the packages we don't want and then check
3662 -- if the remaining graph is broken or not, ie any packages with dangling
3663 -- dependencies. If there are then we cannot prune the given targets.
3664 checkBrokenDeps
3665 :: Graph.Graph ElaboratedPlanPackage
3666 -> Either
3667 CannotPruneDependencies
3668 (Graph.Graph ElaboratedPlanPackage)
3669 checkBrokenDeps graph =
3670 case Graph.broken graph of
3671 [] -> Right graph
3672 brokenPackages ->
3673 Left $
3674 CannotPruneDependencies
3675 [ (pkg, missingDeps)
3676 | (pkg, missingDepIds) <- brokenPackages
3677 , let missingDeps = mapMaybe lookupDep missingDepIds
3679 where
3680 -- lookup in the original unpruned graph
3681 lookupDep = InstallPlan.lookup installPlan
3683 -- | It is not always possible to prune to only the dependencies of a set of
3684 -- targets. It may be the case that removing a package leaves something else
3685 -- that still needed the pruned package.
3687 -- This lists all the packages that would be broken, and their dependencies
3688 -- that would be missing if we did prune.
3689 newtype CannotPruneDependencies
3690 = CannotPruneDependencies
3691 [ ( ElaboratedPlanPackage
3692 , [ElaboratedPlanPackage]
3695 deriving (Show)
3697 -- The other aspects of our Setup.hs policy lives here where we decide on
3698 -- the 'SetupScriptOptions'.
3700 -- Our current policy for the 'SetupCustomImplicitDeps' case is that we
3701 -- try to make the implicit deps cover everything, and we don't allow the
3702 -- compiler to pick up other deps. This may or may not be sustainable, and
3703 -- we might have to allow the deps to be non-exclusive, but that itself would
3704 -- be tricky since we would have to allow the Setup access to all the packages
3705 -- in the store and local dbs.
3707 setupHsScriptOptions
3708 :: ElaboratedReadyPackage
3709 -> ElaboratedInstallPlan
3710 -> ElaboratedSharedConfig
3711 -> DistDirLayout
3712 -> FilePath
3713 -> FilePath
3714 -> Bool
3715 -> Lock
3716 -> SetupScriptOptions
3717 -- TODO: Fix this so custom is a separate component. Custom can ALWAYS
3718 -- be a separate component!!!
3719 setupHsScriptOptions
3720 (ReadyPackage elab@ElaboratedConfiguredPackage{..})
3721 plan
3722 ElaboratedSharedConfig{..}
3723 distdir
3724 srcdir
3725 builddir
3726 isParallelBuild
3727 cacheLock =
3728 SetupScriptOptions
3729 { useCabalVersion = thisVersion elabSetupScriptCliVersion
3730 , useCabalSpecVersion = Just elabSetupScriptCliVersion
3731 , useCompiler = Just pkgConfigCompiler
3732 , usePlatform = Just pkgConfigPlatform
3733 , usePackageDB = elabSetupPackageDBStack
3734 , usePackageIndex = Nothing
3735 , useDependencies =
3736 [ (uid, srcid)
3737 | (ConfiguredId srcid (Just (CLibName LMainLibName)) uid, _) <-
3738 elabSetupDependencies elab
3740 , useDependenciesExclusive = True
3741 , useVersionMacros = elabSetupScriptStyle == SetupCustomExplicitDeps
3742 , useProgramDb = pkgConfigCompilerProgs
3743 , useDistPref = builddir
3744 , useLoggingHandle = Nothing -- this gets set later
3745 , useWorkingDir = Just srcdir
3746 , useExtraPathEnv = elabExeDependencyPaths elab ++ elabProgramPathExtra
3747 , -- note that the above adds the extra-prog-path directly following the elaborated
3748 -- dep paths, so that it overrides the normal path, but _not_ the elaborated extensions
3749 -- for build-tools-depends.
3750 useExtraEnvOverrides = dataDirsEnvironmentForPlan distdir plan
3751 , useWin32CleanHack = False -- TODO: [required eventually]
3752 , forceExternalSetupMethod = isParallelBuild
3753 , setupCacheLock = Just cacheLock
3754 , isInteractive = False
3757 -- | To be used for the input for elaborateInstallPlan.
3759 -- TODO: [code cleanup] make InstallDirs.defaultInstallDirs pure.
3760 userInstallDirTemplates
3761 :: Compiler
3762 -> IO InstallDirs.InstallDirTemplates
3763 userInstallDirTemplates compiler = do
3764 InstallDirs.defaultInstallDirs
3765 (compilerFlavor compiler)
3766 True -- user install
3767 False -- unused
3769 storePackageInstallDirs
3770 :: StoreDirLayout
3771 -> Compiler
3772 -> InstalledPackageId
3773 -> InstallDirs.InstallDirs FilePath
3774 storePackageInstallDirs storeDirLayout compiler ipkgid =
3775 storePackageInstallDirs' storeDirLayout compiler $ newSimpleUnitId ipkgid
3777 storePackageInstallDirs'
3778 :: StoreDirLayout
3779 -> Compiler
3780 -> UnitId
3781 -> InstallDirs.InstallDirs FilePath
3782 storePackageInstallDirs'
3783 StoreDirLayout
3784 { storePackageDirectory
3785 , storeDirectory
3787 compiler
3788 unitid =
3789 InstallDirs.InstallDirs{..}
3790 where
3791 store = storeDirectory compiler
3792 prefix = storePackageDirectory compiler unitid
3793 bindir = prefix </> "bin"
3794 libdir = prefix </> "lib"
3795 libsubdir = ""
3796 -- Note: on macOS, we place libraries into
3797 -- @store/lib@ to work around the load
3798 -- command size limit of macOSs mach-o linker.
3799 -- See also @PackageHash.hashedInstalledPackageIdVeryShort@
3800 dynlibdir
3801 | buildOS == OSX = store </> "lib"
3802 | otherwise = libdir
3803 flibdir = libdir
3804 libexecdir = prefix </> "libexec"
3805 libexecsubdir = ""
3806 includedir = libdir </> "include"
3807 datadir = prefix </> "share"
3808 datasubdir = ""
3809 docdir = datadir </> "doc"
3810 mandir = datadir </> "man"
3811 htmldir = docdir </> "html"
3812 haddockdir = htmldir
3813 sysconfdir = prefix </> "etc"
3815 computeInstallDirs
3816 :: StoreDirLayout
3817 -> InstallDirs.InstallDirTemplates
3818 -> ElaboratedSharedConfig
3819 -> ElaboratedConfiguredPackage
3820 -> InstallDirs.InstallDirs FilePath
3821 computeInstallDirs storeDirLayout defaultInstallDirs elaboratedShared elab
3822 | isInplaceBuildStyle (elabBuildStyle elab) =
3823 -- use the ordinary default install dirs
3824 ( InstallDirs.absoluteInstallDirs
3825 (elabPkgSourceId elab)
3826 (elabUnitId elab)
3827 (compilerInfo (pkgConfigCompiler elaboratedShared))
3828 InstallDirs.NoCopyDest
3829 (pkgConfigPlatform elaboratedShared)
3830 defaultInstallDirs
3832 { -- absoluteInstallDirs sets these as 'undefined' but we have
3833 -- to use them as "Setup.hs configure" args
3834 InstallDirs.libsubdir = ""
3835 , InstallDirs.libexecsubdir = ""
3836 , InstallDirs.datasubdir = ""
3838 | otherwise =
3839 -- use special simplified install dirs
3840 storePackageInstallDirs'
3841 storeDirLayout
3842 (pkgConfigCompiler elaboratedShared)
3843 (elabUnitId elab)
3845 -- TODO: [code cleanup] perhaps reorder this code
3846 -- based on the ElaboratedInstallPlan + ElaboratedSharedConfig,
3847 -- make the various Setup.hs {configure,build,copy} flags
3849 setupHsConfigureFlags
3850 :: ElaboratedInstallPlan
3851 -> ElaboratedReadyPackage
3852 -> ElaboratedSharedConfig
3853 -> Verbosity
3854 -> FilePath
3855 -> Cabal.ConfigFlags
3856 setupHsConfigureFlags
3857 plan
3858 (ReadyPackage elab@ElaboratedConfiguredPackage{..})
3859 sharedConfig@ElaboratedSharedConfig{..}
3860 verbosity
3861 builddir =
3862 sanityCheckElaboratedConfiguredPackage
3863 sharedConfig
3864 elab
3865 (Cabal.ConfigFlags{..})
3866 where
3867 Cabal.ConfigFlags
3868 { configVanillaLib
3869 , configSharedLib
3870 , configStaticLib
3871 , configDynExe
3872 , configFullyStaticExe
3873 , configGHCiLib
3874 , -- , configProfExe -- overridden
3875 configProfLib
3876 , -- , configProf -- overridden
3877 configProfDetail
3878 , configProfLibDetail
3879 , configCoverage
3880 , configLibCoverage
3881 , configRelocatable
3882 , configOptimization
3883 , configSplitSections
3884 , configSplitObjs
3885 , configStripExes
3886 , configStripLibs
3887 , configDebugInfo
3888 } = LBC.buildOptionsConfigFlags elabBuildOptions
3889 configProfExe = mempty
3890 configProf = toFlag $ LBC.withProfExe elabBuildOptions
3892 configArgs = mempty -- unused, passed via args
3893 configDistPref = toFlag builddir
3894 configCabalFilePath = mempty
3895 configVerbosity = toFlag verbosity
3897 configInstantiateWith = Map.toList elabInstantiatedWith
3899 configDeterministic = mempty -- doesn't matter, configIPID/configCID overridese
3900 configIPID = case elabPkgOrComp of
3901 ElabPackage pkg -> toFlag (prettyShow (pkgInstalledId pkg))
3902 ElabComponent _ -> mempty
3903 configCID = case elabPkgOrComp of
3904 ElabPackage _ -> mempty
3905 ElabComponent _ -> toFlag elabComponentId
3907 configProgramPaths = Map.toList elabProgramPaths
3908 configProgramArgs
3909 | {- elabSetupScriptCliVersion < mkVersion [1,24,3] -} True =
3910 -- workaround for <https://github.com/haskell/cabal/issues/4010>
3912 -- It turns out, that even with Cabal 2.0, there's still cases such as e.g.
3913 -- custom Setup.hs scripts calling out to GHC even when going via
3914 -- @runProgram ghcProgram@, as e.g. happy does in its
3915 -- <http://hackage.haskell.org/package/happy-1.19.5/src/Setup.lhs>
3916 -- (see also <https://github.com/haskell/cabal/pull/4433#issuecomment-299396099>)
3918 -- So for now, let's pass the rather harmless and idempotent
3919 -- `-hide-all-packages` flag to all invocations (which has
3920 -- the benefit that every GHC invocation starts with a
3921 -- consistently well-defined clean slate) until we find a
3922 -- better way.
3923 Map.toList $
3924 Map.insertWith
3925 (++)
3926 "ghc"
3927 ["-hide-all-packages"]
3928 elabProgramArgs
3929 configProgramPathExtra = toNubList elabProgramPathExtra
3930 configHcFlavor = toFlag (compilerFlavor pkgConfigCompiler)
3931 configHcPath = mempty -- we use configProgramPaths instead
3932 configHcPkg = mempty -- we use configProgramPaths instead
3933 configDumpBuildInfo = toFlag elabDumpBuildInfo
3935 configConfigurationsFlags = elabFlagAssignment
3936 configConfigureArgs = elabConfigureScriptArgs
3937 configExtraLibDirs = elabExtraLibDirs
3938 configExtraLibDirsStatic = elabExtraLibDirsStatic
3939 configExtraFrameworkDirs = elabExtraFrameworkDirs
3940 configExtraIncludeDirs = elabExtraIncludeDirs
3941 configProgPrefix = maybe mempty toFlag elabProgPrefix
3942 configProgSuffix = maybe mempty toFlag elabProgSuffix
3944 configInstallDirs =
3945 fmap
3946 (toFlag . InstallDirs.toPathTemplate)
3947 elabInstallDirs
3949 -- we only use configDependencies, unless we're talking to an old Cabal
3950 -- in which case we use configConstraints
3951 -- NB: This does NOT use InstallPlan.depends, which includes executable
3952 -- dependencies which should NOT be fed in here (also you don't have
3953 -- enough info anyway)
3955 configDependencies =
3956 [ cidToGivenComponent cid
3957 | (cid, is_internal) <- elabLibDependencies elab
3958 , not is_internal
3961 configPromisedDependencies =
3962 [ cidToGivenComponent cid
3963 | (cid, is_internal) <- elabLibDependencies elab
3964 , is_internal
3967 configConstraints =
3968 case elabPkgOrComp of
3969 ElabPackage _ ->
3970 [ thisPackageVersionConstraint srcid
3971 | (ConfiguredId srcid _ _uid, _) <- elabLibDependencies elab
3973 ElabComponent _ -> []
3975 -- explicitly clear, then our package db stack
3976 -- TODO: [required eventually] have to do this differently for older Cabal versions
3977 configPackageDBs = Nothing : map Just elabBuildPackageDBStack
3979 configTests = case elabPkgOrComp of
3980 ElabPackage pkg -> toFlag (TestStanzas `optStanzaSetMember` pkgStanzasEnabled pkg)
3981 ElabComponent _ -> mempty
3982 configBenchmarks = case elabPkgOrComp of
3983 ElabPackage pkg -> toFlag (BenchStanzas `optStanzaSetMember` pkgStanzasEnabled pkg)
3984 ElabComponent _ -> mempty
3986 configExactConfiguration = toFlag True
3987 configFlagError = mempty -- TODO: [research required] appears not to be implemented
3988 configScratchDir = mempty -- never use
3989 configUserInstall = mempty -- don't rely on defaults
3990 configPrograms_ = mempty -- never use, shouldn't exist
3991 configUseResponseFiles = mempty
3992 configAllowDependingOnPrivateLibs = Flag $ not $ libraryVisibilitySupported pkgConfigCompiler
3994 cidToGivenComponent :: ConfiguredId -> GivenComponent
3995 cidToGivenComponent (ConfiguredId srcid mb_cn cid) = GivenComponent (packageName srcid) ln cid
3996 where
3997 ln = case mb_cn of
3998 Just (CLibName lname) -> lname
3999 Just _ -> error "non-library dependency"
4000 Nothing -> LMainLibName
4002 configCoverageFor = determineCoverageFor elabPkgSourceId plan
4004 setupHsConfigureArgs
4005 :: ElaboratedConfiguredPackage
4006 -> [String]
4007 setupHsConfigureArgs (ElaboratedConfiguredPackage{elabPkgOrComp = ElabPackage _}) = []
4008 setupHsConfigureArgs elab@(ElaboratedConfiguredPackage{elabPkgOrComp = ElabComponent comp}) =
4009 [showComponentTarget (packageId elab) (ComponentTarget cname WholeComponent)]
4010 where
4011 cname =
4012 fromMaybe
4013 (error "setupHsConfigureArgs: trying to configure setup")
4014 (compComponentName comp)
4016 setupHsBuildFlags
4017 :: Flag String
4018 -> ElaboratedConfiguredPackage
4019 -> ElaboratedSharedConfig
4020 -> Verbosity
4021 -> FilePath
4022 -> Cabal.BuildFlags
4023 setupHsBuildFlags par_strat elab _ verbosity builddir =
4024 Cabal.BuildFlags
4025 { buildProgramPaths = mempty -- unused, set at configure time
4026 , buildProgramArgs = mempty -- unused, set at configure time
4027 , buildVerbosity = toFlag verbosity
4028 , buildDistPref = toFlag builddir
4029 , buildNumJobs = mempty -- TODO: [nice to have] sometimes want to use toFlag (Just numBuildJobs),
4030 , buildUseSemaphore =
4031 if elabSetupScriptCliVersion elab >= mkVersion [3, 11, 0, 0]
4032 then -- Cabal 3.11 is the first version that supports parallelism semaphores
4033 par_strat
4034 else mempty
4035 , buildArgs = mempty -- unused, passed via args not flags
4036 , buildCabalFilePath = mempty
4039 setupHsBuildArgs :: ElaboratedConfiguredPackage -> [String]
4040 setupHsBuildArgs elab@(ElaboratedConfiguredPackage{elabPkgOrComp = ElabPackage _})
4041 -- Fix for #3335, don't pass build arguments if it's not supported
4042 | elabSetupScriptCliVersion elab >= mkVersion [1, 17] =
4043 map (showComponentTarget (packageId elab)) (elabBuildTargets elab)
4044 | otherwise =
4046 setupHsBuildArgs (ElaboratedConfiguredPackage{elabPkgOrComp = ElabComponent _}) =
4049 setupHsTestFlags
4050 :: ElaboratedConfiguredPackage
4051 -> Verbosity
4052 -> FilePath
4053 -> Cabal.TestFlags
4054 setupHsTestFlags (ElaboratedConfiguredPackage{..}) verbosity builddir =
4055 Cabal.TestFlags
4056 { testDistPref = toFlag builddir
4057 , testVerbosity = toFlag verbosity
4058 , testMachineLog = maybe mempty toFlag elabTestMachineLog
4059 , testHumanLog = maybe mempty toFlag elabTestHumanLog
4060 , testShowDetails = maybe (Flag Cabal.Always) toFlag elabTestShowDetails
4061 , testKeepTix = toFlag elabTestKeepTix
4062 , testWrapper = maybe mempty toFlag elabTestWrapper
4063 , testFailWhenNoTestSuites = toFlag elabTestFailWhenNoTestSuites
4064 , testOptions = elabTestTestOptions
4067 setupHsTestArgs :: ElaboratedConfiguredPackage -> [String]
4068 -- TODO: Does the issue #3335 affects test as well
4069 setupHsTestArgs elab =
4070 mapMaybe (showTestComponentTarget (packageId elab)) (elabTestTargets elab)
4072 setupHsBenchFlags
4073 :: ElaboratedConfiguredPackage
4074 -> ElaboratedSharedConfig
4075 -> Verbosity
4076 -> FilePath
4077 -> Cabal.BenchmarkFlags
4078 setupHsBenchFlags (ElaboratedConfiguredPackage{..}) _ verbosity builddir =
4079 Cabal.BenchmarkFlags
4080 { benchmarkDistPref = toFlag builddir
4081 , benchmarkVerbosity = toFlag verbosity
4082 , benchmarkOptions = elabBenchmarkOptions
4085 setupHsBenchArgs :: ElaboratedConfiguredPackage -> [String]
4086 setupHsBenchArgs elab =
4087 mapMaybe (showBenchComponentTarget (packageId elab)) (elabBenchTargets elab)
4089 setupHsReplFlags
4090 :: ElaboratedConfiguredPackage
4091 -> ElaboratedSharedConfig
4092 -> Verbosity
4093 -> FilePath
4094 -> Cabal.ReplFlags
4095 setupHsReplFlags _ sharedConfig verbosity builddir =
4096 Cabal.ReplFlags
4097 { replProgramPaths = mempty -- unused, set at configure time
4098 , replProgramArgs = mempty -- unused, set at configure time
4099 , replVerbosity = toFlag verbosity
4100 , replDistPref = toFlag builddir
4101 , replReload = mempty -- only used as callback from repl
4102 , replReplOptions = pkgConfigReplOptions sharedConfig -- runtime override for repl flags
4105 setupHsReplArgs :: ElaboratedConfiguredPackage -> [String]
4106 setupHsReplArgs elab =
4107 map (\t -> showComponentTarget (packageId elab) t) (elabReplTarget elab)
4109 setupHsCopyFlags
4110 :: ElaboratedConfiguredPackage
4111 -> ElaboratedSharedConfig
4112 -> Verbosity
4113 -> FilePath
4114 -> FilePath
4115 -> Cabal.CopyFlags
4116 setupHsCopyFlags _ _ verbosity builddir destdir =
4117 Cabal.CopyFlags
4118 { copyArgs = [] -- TODO: could use this to only copy what we enabled
4119 , copyDest = toFlag (InstallDirs.CopyTo destdir)
4120 , copyDistPref = toFlag builddir
4121 , copyVerbosity = toFlag verbosity
4122 , copyCabalFilePath = mempty
4125 setupHsRegisterFlags
4126 :: ElaboratedConfiguredPackage
4127 -> ElaboratedSharedConfig
4128 -> Verbosity
4129 -> FilePath
4130 -> FilePath
4131 -> Cabal.RegisterFlags
4132 setupHsRegisterFlags
4133 ElaboratedConfiguredPackage{..}
4135 verbosity
4136 builddir
4137 pkgConfFile =
4138 Cabal.RegisterFlags
4139 { regPackageDB = mempty -- misfeature
4140 , regGenScript = mempty -- never use
4141 , regGenPkgConf = toFlag (Just pkgConfFile)
4142 , regInPlace = case elabBuildStyle of
4143 BuildInplaceOnly{} -> toFlag True
4144 BuildAndInstall -> toFlag False
4145 , regPrintId = mempty -- never use
4146 , regDistPref = toFlag builddir
4147 , regArgs = []
4148 , regVerbosity = toFlag verbosity
4149 , regCabalFilePath = mempty
4152 setupHsHaddockFlags
4153 :: ElaboratedConfiguredPackage
4154 -> ElaboratedSharedConfig
4155 -> Verbosity
4156 -> FilePath
4157 -> Cabal.HaddockFlags
4158 setupHsHaddockFlags (ElaboratedConfiguredPackage{..}) (ElaboratedSharedConfig{..}) verbosity builddir =
4159 Cabal.HaddockFlags
4160 { haddockProgramPaths =
4161 case lookupProgram haddockProgram pkgConfigCompilerProgs of
4162 Nothing -> mempty
4163 Just prg ->
4165 ( programName haddockProgram
4166 , locationPath (programLocation prg)
4169 , haddockProgramArgs = mempty -- unused, set at configure time
4170 , haddockHoogle = toFlag elabHaddockHoogle
4171 , haddockHtml = toFlag elabHaddockHtml
4172 , haddockHtmlLocation = maybe mempty toFlag elabHaddockHtmlLocation
4173 , haddockForHackage = toFlag elabHaddockForHackage
4174 , haddockForeignLibs = toFlag elabHaddockForeignLibs
4175 , haddockExecutables = toFlag elabHaddockExecutables
4176 , haddockTestSuites = toFlag elabHaddockTestSuites
4177 , haddockBenchmarks = toFlag elabHaddockBenchmarks
4178 , haddockInternal = toFlag elabHaddockInternal
4179 , haddockCss = maybe mempty toFlag elabHaddockCss
4180 , haddockLinkedSource = toFlag elabHaddockLinkedSource
4181 , haddockQuickJump = toFlag elabHaddockQuickJump
4182 , haddockHscolourCss = maybe mempty toFlag elabHaddockHscolourCss
4183 , haddockContents = maybe mempty toFlag elabHaddockContents
4184 , haddockDistPref = toFlag builddir
4185 , haddockKeepTempFiles = mempty -- TODO: from build settings
4186 , haddockVerbosity = toFlag verbosity
4187 , haddockCabalFilePath = mempty
4188 , haddockIndex = maybe mempty toFlag elabHaddockIndex
4189 , haddockBaseUrl = maybe mempty toFlag elabHaddockBaseUrl
4190 , haddockLib = maybe mempty toFlag elabHaddockLib
4191 , haddockOutputDir = maybe mempty toFlag elabHaddockOutputDir
4192 , haddockArgs = mempty
4195 setupHsHaddockArgs :: ElaboratedConfiguredPackage -> [String]
4196 -- TODO: Does the issue #3335 affects test as well
4197 setupHsHaddockArgs elab =
4198 map (showComponentTarget (packageId elab)) (elabHaddockTargets elab)
4200 ------------------------------------------------------------------------------
4202 -- * Sharing installed packages
4204 ------------------------------------------------------------------------------
4207 -- Nix style store management for tarball packages
4209 -- So here's our strategy:
4211 -- We use a per-user nix-style hashed store, but /only/ for tarball packages.
4212 -- So that includes packages from hackage repos (and other http and local
4213 -- tarballs). For packages in local directories we do not register them into
4214 -- the shared store by default, we just build them locally inplace.
4216 -- The reason we do it like this is that it's easy to make stable hashes for
4217 -- tarball packages, and these packages benefit most from sharing. By contrast
4218 -- unpacked dir packages are harder to hash and they tend to change more
4219 -- frequently so there's less benefit to sharing them.
4221 -- When using the nix store approach we have to run the solver *without*
4222 -- looking at the packages installed in the store, just at the source packages
4223 -- (plus core\/global installed packages). Then we do a post-processing pass
4224 -- to replace configured packages in the plan with pre-existing ones, where
4225 -- possible. Where possible of course means where the nix-style package hash
4226 -- equals one that's already in the store.
4228 -- One extra wrinkle is that unless we know package tarball hashes upfront, we
4229 -- will have to download the tarballs to find their hashes. So we have two
4230 -- options: delay replacing source with pre-existing installed packages until
4231 -- the point during the execution of the install plan where we have the
4232 -- tarball, or try to do as much up-front as possible and then check again
4233 -- during plan execution. The former isn't great because we would end up
4234 -- telling users we're going to re-install loads of packages when in fact we
4235 -- would just share them. It'd be better to give as accurate a prediction as
4236 -- we can. The latter is better for users, but we do still have to check
4237 -- during plan execution because it's important that we don't replace existing
4238 -- installed packages even if they have the same package hash, because we
4239 -- don't guarantee ABI stability.
4241 -- TODO: [required eventually] for safety of concurrent installs, we must make sure we register but
4242 -- not replace installed packages with ghc-pkg.
4244 packageHashInputs
4245 :: ElaboratedSharedConfig
4246 -> ElaboratedConfiguredPackage
4247 -> PackageHashInputs
4248 packageHashInputs
4249 pkgshared
4250 elab@( ElaboratedConfiguredPackage
4251 { elabPkgSourceHash = Just srchash
4254 PackageHashInputs
4255 { pkgHashPkgId = packageId elab
4256 , pkgHashComponent =
4257 case elabPkgOrComp elab of
4258 ElabPackage _ -> Nothing
4259 ElabComponent comp -> Just (compSolverName comp)
4260 , pkgHashSourceHash = srchash
4261 , pkgHashPkgConfigDeps = Set.fromList (elabPkgConfigDependencies elab)
4262 , pkgHashDirectDeps =
4263 case elabPkgOrComp elab of
4264 ElabPackage (ElaboratedPackage{..}) ->
4265 Set.fromList $
4266 [ confInstId dep
4267 | (dep, _) <- CD.select relevantDeps pkgLibDependencies
4269 ++ [ confInstId dep
4270 | dep <- CD.select relevantDeps pkgExeDependencies
4272 ElabComponent comp ->
4273 Set.fromList
4274 ( map
4275 confInstId
4276 ( map fst (compLibDependencies comp)
4277 ++ compExeDependencies comp
4280 , pkgHashOtherConfig = packageHashConfigInputs pkgshared elab
4282 where
4283 -- Obviously the main deps are relevant
4284 relevantDeps CD.ComponentLib = True
4285 relevantDeps (CD.ComponentSubLib _) = True
4286 relevantDeps (CD.ComponentFLib _) = True
4287 relevantDeps (CD.ComponentExe _) = True
4288 -- Setup deps can affect the Setup.hs behaviour and thus what is built
4289 relevantDeps CD.ComponentSetup = True
4290 -- However testsuites and benchmarks do not get installed and should not
4291 -- affect the result, so we do not include them.
4292 relevantDeps (CD.ComponentTest _) = False
4293 relevantDeps (CD.ComponentBench _) = False
4294 packageHashInputs _ pkg =
4295 error $
4296 "packageHashInputs: only for packages with source hashes. "
4297 ++ prettyShow (packageId pkg)
4299 packageHashConfigInputs
4300 :: ElaboratedSharedConfig
4301 -> ElaboratedConfiguredPackage
4302 -> PackageHashConfigInputs
4303 packageHashConfigInputs shared@ElaboratedSharedConfig{..} pkg =
4304 PackageHashConfigInputs
4305 { pkgHashCompilerId = compilerId pkgConfigCompiler
4306 , pkgHashPlatform = pkgConfigPlatform
4307 , pkgHashFlagAssignment = elabFlagAssignment
4308 , pkgHashConfigureScriptArgs = elabConfigureScriptArgs
4309 , pkgHashVanillaLib = withVanillaLib
4310 , pkgHashSharedLib = withSharedLib
4311 , pkgHashDynExe = withDynExe
4312 , pkgHashFullyStaticExe = withFullyStaticExe
4313 , pkgHashGHCiLib = withGHCiLib
4314 , pkgHashProfLib = withProfLib
4315 , pkgHashProfExe = withProfExe
4316 , pkgHashProfLibDetail = withProfLibDetail
4317 , pkgHashProfExeDetail = withProfExeDetail
4318 , pkgHashCoverage = exeCoverage
4319 , pkgHashOptimization = withOptimization
4320 , pkgHashSplitSections = splitSections
4321 , pkgHashSplitObjs = splitObjs
4322 , pkgHashStripLibs = stripLibs
4323 , pkgHashStripExes = stripExes
4324 , pkgHashDebugInfo = withDebugInfo
4325 , pkgHashProgramArgs = elabProgramArgs
4326 , pkgHashExtraLibDirs = elabExtraLibDirs
4327 , pkgHashExtraLibDirsStatic = elabExtraLibDirsStatic
4328 , pkgHashExtraFrameworkDirs = elabExtraFrameworkDirs
4329 , pkgHashExtraIncludeDirs = elabExtraIncludeDirs
4330 , pkgHashProgPrefix = elabProgPrefix
4331 , pkgHashProgSuffix = elabProgSuffix
4332 , pkgHashPackageDbs = elabPackageDbs
4333 , pkgHashDocumentation = elabBuildHaddocks
4334 , pkgHashHaddockHoogle = elabHaddockHoogle
4335 , pkgHashHaddockHtml = elabHaddockHtml
4336 , pkgHashHaddockHtmlLocation = elabHaddockHtmlLocation
4337 , pkgHashHaddockForeignLibs = elabHaddockForeignLibs
4338 , pkgHashHaddockExecutables = elabHaddockExecutables
4339 , pkgHashHaddockTestSuites = elabHaddockTestSuites
4340 , pkgHashHaddockBenchmarks = elabHaddockBenchmarks
4341 , pkgHashHaddockInternal = elabHaddockInternal
4342 , pkgHashHaddockCss = elabHaddockCss
4343 , pkgHashHaddockLinkedSource = elabHaddockLinkedSource
4344 , pkgHashHaddockQuickJump = elabHaddockQuickJump
4345 , pkgHashHaddockContents = elabHaddockContents
4346 , pkgHashHaddockIndex = elabHaddockIndex
4347 , pkgHashHaddockBaseUrl = elabHaddockBaseUrl
4348 , pkgHashHaddockLib = elabHaddockLib
4349 , pkgHashHaddockOutputDir = elabHaddockOutputDir
4351 where
4352 ElaboratedConfiguredPackage{..} = normaliseConfiguredPackage shared pkg
4353 LBC.BuildOptions{..} = elabBuildOptions
4355 -- | Given the 'InstalledPackageIndex' for a nix-style package store, and an
4356 -- 'ElaboratedInstallPlan', replace configured source packages by installed
4357 -- packages from the store whenever they exist.
4358 improveInstallPlanWithInstalledPackages
4359 :: Set UnitId
4360 -> ElaboratedInstallPlan
4361 -> ElaboratedInstallPlan
4362 improveInstallPlanWithInstalledPackages installedPkgIdSet =
4363 InstallPlan.installed canPackageBeImproved
4364 where
4365 canPackageBeImproved pkg =
4366 installedUnitId pkg `Set.member` installedPkgIdSet
4368 -- TODO: sanity checks:
4369 -- \* the installed package must have the expected deps etc
4370 -- \* the installed package must not be broken, valid dep closure
4372 -- TODO: decide what to do if we encounter broken installed packages,
4373 -- since overwriting is never safe.
4375 -- Path construction
4376 ------
4378 -- | The path to the directory that contains a specific executable.
4379 -- NB: For inplace NOT InstallPaths.bindir installDirs; for an
4380 -- inplace build those values are utter nonsense. So we
4381 -- have to guess where the directory is going to be.
4382 -- Fortunately this is "stable" part of Cabal API.
4383 -- But the way we get the build directory is A HORRIBLE
4384 -- HACK.
4385 binDirectoryFor
4386 :: DistDirLayout
4387 -> ElaboratedSharedConfig
4388 -> ElaboratedConfiguredPackage
4389 -> FilePath
4390 -> FilePath
4391 binDirectoryFor layout config package exe = case elabBuildStyle package of
4392 BuildAndInstall -> installedBinDirectory package
4393 BuildInplaceOnly{} -> inplaceBinRoot layout config package </> exe
4395 -- package has been built and installed.
4396 installedBinDirectory :: ElaboratedConfiguredPackage -> FilePath
4397 installedBinDirectory = InstallDirs.bindir . elabInstallDirs
4399 -- | The path to the @build@ directory for an inplace build.
4400 inplaceBinRoot
4401 :: DistDirLayout
4402 -> ElaboratedSharedConfig
4403 -> ElaboratedConfiguredPackage
4404 -> FilePath
4405 inplaceBinRoot layout config package =
4406 distBuildDirectory layout (elabDistDirParams config package)
4407 </> "build"
4409 --------------------------------------------------------------------------------
4410 -- Configure --coverage-for flags
4412 -- The list of non-pre-existing libraries without module holes, i.e. the
4413 -- main library and sub-libraries components of all the local packages in
4414 -- the project that do not require instantiations or are instantiations.
4415 determineCoverageFor
4416 :: PackageId
4417 -- ^ The 'PackageId' of the package or component being configured
4418 -> ElaboratedInstallPlan
4419 -> Flag [UnitId]
4420 determineCoverageFor configuredPkgSourceId plan =
4421 Flag
4422 $ mapMaybe
4423 ( \case
4424 InstallPlan.Installed elab
4425 | shouldCoverPkg elab -> Just $ elabUnitId elab
4426 InstallPlan.Configured elab
4427 | shouldCoverPkg elab -> Just $ elabUnitId elab
4428 _ -> Nothing
4430 $ Graph.toList
4431 $ InstallPlan.toGraph plan
4432 where
4433 shouldCoverPkg elab@ElaboratedConfiguredPackage{elabModuleShape, elabPkgSourceId, elabLocalToProject} =
4434 elabLocalToProject
4435 && not (isIndefiniteOrInstantiation elabModuleShape)
4436 -- TODO(#9493): We can only cover libraries in the same package
4437 -- as the testsuite
4438 && configuredPkgSourceId == elabPkgSourceId
4439 -- Libraries only! We don't cover testsuite modules, so we never need
4440 -- the paths to their mix dirs. Furthermore, we do not install testsuites...
4441 && maybe False (\case CLibName{} -> True; CNotLibName{} -> False) (elabComponentName elab)
4443 isIndefiniteOrInstantiation :: ModuleShape -> Bool
4444 isIndefiniteOrInstantiation = not . Set.null . modShapeRequires