2 {-# LANGUAGE DeriveDataTypeable #-}
3 {-# LANGUAGE DeriveFunctor #-}
4 {-# LANGUAGE LambdaCase #-}
5 {-# LANGUAGE NamedFieldPuns #-}
6 {-# LANGUAGE RankNTypes #-}
7 {-# LANGUAGE RecordWildCards #-}
8 {-# LANGUAGE TypeFamilies #-}
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
40 , ElaboratedConfiguredPackage
(..)
41 , ElaboratedPlanPackage
42 , ElaboratedSharedConfig
(..)
43 , ElaboratedReadyPackage
47 -- * Reading the project configuration
48 -- $readingTheProjectConfiguration
49 , rebuildProjectConfig
51 -- * Producing the elaborated install plan
56 , AvailableTarget
(..)
57 , AvailableTargetStatus
(..)
58 , TargetRequested
(..)
59 , ComponentTarget
(..)
60 , SubComponentTarget
(..)
64 -- * Selecting a plan subset
65 , pruneInstallPlanToTargets
67 , pruneInstallPlanToDependencies
68 , CannotPruneDependencies
(..)
70 -- * Utils required for building
71 , pkgHasEphemeralBuildTargets
72 , elabBuildTargetWholeComponents
75 -- * Setup.hs CLI flags for building
76 , setupHsScriptOptions
77 , setupHsConfigureFlags
78 , setupHsConfigureArgs
88 , setupHsRegisterFlags
93 -- * Path construction
96 , storePackageInstallDirs
97 , storePackageInstallDirs
'
100 import Distribution
.Client
.Compat
.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
(..)
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
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 Distribution
.Types
.PackageVersionConstraint
174 import Distribution
.Types
.PkgconfigDependency
175 import Distribution
.Types
.UnqualComponentName
177 import Distribution
.Backpack
178 import Distribution
.Backpack
.ComponentsGraph
179 import Distribution
.Backpack
.ConfiguredComponent
180 import Distribution
.Backpack
.FullUnitId
181 import Distribution
.Backpack
.LinkedComponent
182 import Distribution
.Backpack
.ModuleShape
184 import Distribution
.Simple
.Utils
185 import Distribution
.Version
187 import qualified Distribution
.InstalledPackageInfo
as IPI
188 import qualified Distribution
.PackageDescription
as PD
189 import qualified Distribution
.PackageDescription
.Configuration
as PD
190 import qualified Distribution
.Simple
.Configure
as Cabal
191 import qualified Distribution
.Simple
.GHC
as GHC
192 import qualified Distribution
.Simple
.GHCJS
as GHCJS
193 import qualified Distribution
.Simple
.InstallDirs
as InstallDirs
194 import qualified Distribution
.Simple
.LocalBuildInfo
as Cabal
195 import qualified Distribution
.Simple
.Setup
as Cabal
196 import qualified Distribution
.Solver
.Types
.ComponentDeps
as CD
198 import qualified Distribution
.Compat
.Graph
as Graph
200 import Control
.Exception
(assert
)
201 import Control
.Monad
(forM
, sequence)
202 import Control
.Monad
.IO.Class
(liftIO
)
203 import Control
.Monad
.State
as State
(State
, execState
, runState
, state
)
204 import Data
.Foldable
(fold
)
205 import Data
.List
(deleteBy, groupBy)
206 import qualified Data
.List
.NonEmpty
as NE
207 import qualified Data
.Map
as Map
208 import qualified Data
.Set
as Set
209 import Distribution
.Client
.Errors
210 import System
.FilePath
211 import Text
.PrettyPrint
(colon
, comma
, fsep
, hang
, punctuate
, quotes
, text
, vcat
, ($$))
212 import qualified Text
.PrettyPrint
as Disp
214 -- | Check that an 'ElaboratedConfiguredPackage' actually makes
215 -- sense under some 'ElaboratedSharedConfig'.
216 sanityCheckElaboratedConfiguredPackage
217 :: ElaboratedSharedConfig
218 -> ElaboratedConfiguredPackage
221 sanityCheckElaboratedConfiguredPackage
223 elab
@ElaboratedConfiguredPackage
{..} =
224 ( case elabPkgOrComp
of
225 ElabPackage pkg
-> sanityCheckElaboratedPackage elab pkg
226 ElabComponent comp
-> sanityCheckElaboratedComponent elab comp
228 -- The assertion below fails occasionally for unknown reason
229 -- so it was muted until we figure it out, otherwise it severely
230 -- hinders our ability to share and test development builds of cabal-install.
231 -- Tracking issue: https://github.com/haskell/cabal/issues/6006
233 -- either a package is being built inplace, or the
234 -- 'installedPackageId' we assigned is consistent with
235 -- the 'hashedInstalledPackageId' we would compute from
236 -- the elaborated configured package
238 ( isInplaceBuildStyle elabBuildStyle
240 == hashedInstalledPackageId
241 (packageHashInputs sharedConfig elab
)
243 -- the stanzas explicitly disabled should not be available
246 optStanzaKeysFilteredByValue
(maybe False not) elabStanzasRequested `optStanzaSetIntersection` elabStanzasAvailable
248 -- either a package is built inplace, or we are not attempting to
249 -- build any test suites or benchmarks (we never build these
250 -- for remote packages!)
252 ( isInplaceBuildStyle elabBuildStyle
253 || optStanzaSetNull elabStanzasAvailable
256 sanityCheckElaboratedComponent
257 :: ElaboratedConfiguredPackage
258 -> ElaboratedComponent
261 sanityCheckElaboratedComponent
262 ElaboratedConfiguredPackage
{..}
263 ElaboratedComponent
{..} =
264 -- Should not be building bench or test if not inplace.
266 ( isInplaceBuildStyle elabBuildStyle
267 ||
case compComponentName
of
269 Just
(CLibName _
) -> True
270 Just
(CExeName _
) -> True
271 -- This is interesting: there's no way to declare a dependency
272 -- on a foreign library at the moment, but you may still want
273 -- to install these to the store
274 Just
(CFLibName _
) -> True
275 Just
(CBenchName _
) -> False
276 Just
(CTestName _
) -> False
279 sanityCheckElaboratedPackage
280 :: ElaboratedConfiguredPackage
284 sanityCheckElaboratedPackage
285 ElaboratedConfiguredPackage
{..}
286 ElaboratedPackage
{..} =
287 -- we should only have enabled stanzas that actually can be built
288 -- (according to the solver)
289 assert
(pkgStanzasEnabled `optStanzaSetIsSubset` elabStanzasAvailable
)
290 -- the stanzas that the user explicitly requested should be
291 -- enabled (by the previous test, they are also available)
293 ( optStanzaKeysFilteredByValue
(fromMaybe False) elabStanzasRequested
294 `optStanzaSetIsSubset` pkgStanzasEnabled
297 -- $readingTheProjectConfiguration
299 -- The project configuration is assembled into a ProjectConfig as follows:
301 -- CLI arguments are converted using "commandLineFlagsToProjectConfig" in the
302 -- v2 command entrypoints and passed to "establishProjectBaseContext" which
303 -- then calls "rebuildProjectConfig".
305 -- "rebuildProjectConfig" then calls "readProjectConfig" to read the project
306 -- files. Due to the presence of conditionals, this output is in the form of a
307 -- "ProjectConfigSkeleton" and will be resolved by "rebuildProjectConfig" using
308 -- "instantiateProjectConfigSkeletonFetchingCompiler".
310 -- "readProjectConfig" also loads the global configuration, which is read with
311 -- "loadConfig" and convertd to a "ProjectConfig" with "convertLegacyGlobalConfig".
313 -- *Important:* You can notice how some project config options are needed to read the
314 -- project config! This is evident by the fact that "rebuildProjectConfig"
315 -- takes "HttpTransport" and "DistDirLayout" as parameters. Two arguments are
316 -- infact determined from the CLI alone (in "establishProjectBaseContext").
317 -- Consequently, project files (including global configuration) cannot
318 -- affect those parameters!
320 -- Furthermore, the project configuration can specify a compiler to use,
321 -- which we need to resolve the conditionals in the project configuration!
322 -- To solve this, we configure the compiler from what is obtained by applying
323 -- the CLI configuration over the the configuration obtained by "flattening"
324 -- ProjectConfigSkeleton. This means collapsing all conditionals by taking
327 -- | Return the up-to-date project config and information about the local
328 -- packages within the project.
336 , [PackageSpecifier UnresolvedSourcePackage
]
341 distDirLayout
@DistDirLayout
342 { distProjectRootDirectory
344 , distProjectCacheFile
345 , distProjectCacheDirectory
349 progsearchpath
<- liftIO
$ getSystemSearchPath
351 let fileMonitorProjectConfig
= newFileMonitor
(distProjectCacheFile
"config")
353 fileMonitorProjectConfigKey
<- do
354 configPath
<- getConfigFilePath projectConfigConfigFile
358 , (projectConfigHcFlavor
, projectConfigHcPath
, projectConfigHcPkg
)
360 , packageConfigProgramPaths
361 , packageConfigProgramPathExtra
364 (projectConfig
, localPackages
) <-
365 runRebuild distProjectRootDirectory
368 fileMonitorProjectConfig
369 fileMonitorProjectConfigKey
-- todo check deps too?
371 liftIO
$ info verbosity
"Project settings changed, reconfiguring..."
372 projectConfigSkeleton
<- phaseReadProjectConfig
373 let fetchCompiler
= do
374 -- have to create the cache directory before configuring the compiler
375 liftIO
$ createDirectoryIfMissingVerbose verbosity
True distProjectCacheDirectory
376 (compiler
, Platform arch os
, _
) <- configureCompiler verbosity distDirLayout
(fst (PD
.ignoreConditions projectConfigSkeleton
) <> cliConfig
)
377 pure
(os
, arch
, compilerInfo compiler
)
379 projectConfig
<- instantiateProjectConfigSkeletonFetchingCompiler fetchCompiler mempty projectConfigSkeleton
380 when (projectConfigDistDir
(projectConfigShared
$ projectConfig
) /= NoFlag
) $
382 warn verbosity
"The builddir option is not supported in project and config files. It will be ignored."
383 localPackages
<- phaseReadLocalPackages
(projectConfig
<> cliConfig
)
384 return (projectConfig
, localPackages
)
388 ("this build was affected by the following (project) config files:" :) $
390 | Explicit path
<- Set
.toList
$ projectConfigProvenance projectConfig
393 return (projectConfig
<> cliConfig
, localPackages
)
395 ProjectConfigShared
{projectConfigHcFlavor
, projectConfigHcPath
, projectConfigHcPkg
, projectConfigIgnoreProject
, projectConfigConfigFile
} =
396 projectConfigShared cliConfig
398 PackageConfig
{packageConfigProgramPaths
, packageConfigProgramPathExtra
} =
399 projectConfigLocalPackages cliConfig
401 -- Read the cabal.project (or implicit config) and combine it with
402 -- arguments from the command line
404 phaseReadProjectConfig
:: Rebuild ProjectConfigSkeleton
405 phaseReadProjectConfig
= do
406 readProjectConfig verbosity httpTransport projectConfigIgnoreProject projectConfigConfigFile distDirLayout
408 -- Look for all the cabal packages in the project
409 -- some of which may be local src dirs, tarballs etc
411 phaseReadLocalPackages
413 -> Rebuild
[PackageSpecifier UnresolvedSourcePackage
]
414 phaseReadLocalPackages
415 projectConfig
@ProjectConfig
416 { projectConfigShared
417 , projectConfigBuildOnly
419 pkgLocations
<- findProjectPackages distDirLayout projectConfig
420 -- Create folder only if findProjectPackages did not throw a
421 -- BadPackageLocations exception.
423 createDirectoryIfMissingVerbose verbosity
True distDirectory
424 createDirectoryIfMissingVerbose verbosity
True distProjectCacheDirectory
426 fetchAndReadSourcePackages
430 projectConfigBuildOnly
437 -> Rebuild
(Compiler
, Platform
, ProgramDb
)
441 { distProjectCacheFile
444 { projectConfigShared
=
446 { projectConfigHcFlavor
447 , projectConfigHcPath
450 , projectConfigLocalPackages
=
452 { packageConfigProgramPaths
453 , packageConfigProgramPathExtra
456 let fileMonitorCompiler
= newFileMonitor
. distProjectCacheFile
$ "compiler"
458 progsearchpath
<- liftIO
$ getSystemSearchPath
466 , packageConfigProgramPaths
467 , packageConfigProgramPathExtra
470 liftIO
$ info verbosity
"Compiler settings changed, reconfiguring..."
471 result
@(_
, _
, progdb
') <-
473 Cabal
.configCompilerEx
480 -- Note that we added the user-supplied program locations and args
481 -- for /all/ programs, not just those for the compiler prog and
482 -- compiler-related utils. In principle we don't know which programs
483 -- the compiler will configure (and it does vary between compilers).
484 -- We do know however that the compiler will only configure the
485 -- programs it cares about, and those are the ones we monitor here.
486 monitorFiles
(programsMonitorFiles progdb
')
490 hcFlavor
= flagToMaybe projectConfigHcFlavor
491 hcPath
= flagToMaybe projectConfigHcPath
492 hcPkg
= flagToMaybe projectConfigHcPkg
494 userSpecifyPaths
(Map
.toList
(getMapLast packageConfigProgramPaths
))
495 . modifyProgramSearchPath
496 ( [ ProgramSearchPathDir dir
497 | dir
<- fromNubList packageConfigProgramPathExtra
503 ------------------------------------------------------------------------------
505 -- * Deciding what to do: making an 'ElaboratedInstallPlan'
507 ------------------------------------------------------------------------------
509 -- | Return an up-to-date elaborated install plan.
511 -- Two variants of the install plan are returned: with and without packages
512 -- from the store. That is, the \"improved\" plan where source packages are
513 -- replaced by pre-existing installed packages from the store (when their ids
514 -- match), and also the original elaborated plan which uses primarily source
517 -- The improved plan is what we use for building, but the original elaborated
518 -- plan is useful for reporting and configuration. For example the @freeze@
519 -- command needs the source package info to know about flag choices and
520 -- dependencies of executables and setup scripts.
527 -> [PackageSpecifier UnresolvedSourcePackage
]
528 -> Maybe InstalledPackageIndex
530 ( ElaboratedInstallPlan
-- with store packages
531 , ElaboratedInstallPlan
-- with source packages
532 , ElaboratedSharedConfig
533 , IndexUtils
.TotalIndexState
534 , IndexUtils
.ActiveRepos
536 -- ^ @(improvedPlan, elaboratedPlan, _, _, _)@
539 distDirLayout
@DistDirLayout
540 { distProjectRootDirectory
541 , distProjectCacheFile
544 { cabalStoreDirLayout
545 } = \projectConfig localPackages mbInstalledPackages
->
546 runRebuild distProjectRootDirectory
$ do
547 progsearchpath
<- liftIO
$ getSystemSearchPath
548 let projectConfigMonitored
= projectConfig
{projectConfigBuildOnly
= mempty
}
550 -- The overall improved plan is cached
553 fileMonitorImprovedPlan
554 -- react to changes in the project config,
555 -- the package .cabal files and the path
556 (projectConfigMonitored
, localPackages
, progsearchpath
)
558 -- And so is the elaborated plan that the improved plan based on
559 (elaboratedPlan
, elaboratedShared
, totalIndexState
, activeRepos
) <-
562 fileMonitorElaboratedPlan
563 ( projectConfigMonitored
568 compilerEtc
<- phaseConfigureCompiler projectConfig
569 _
<- phaseConfigurePrograms projectConfig compilerEtc
570 (solverPlan
, pkgConfigDB
, totalIndexState
, activeRepos
) <-
575 (fromMaybe mempty mbInstalledPackages
)
586 phaseMaintainPlanOutputs elaboratedPlan elaboratedShared
587 return (elaboratedPlan
, elaboratedShared
, totalIndexState
, activeRepos
)
589 -- The improved plan changes each time we install something, whereas
590 -- the underlying elaborated plan only changes when input config
591 -- changes, so it's worth caching them separately.
592 improvedPlan
<- phaseImprovePlan elaboratedPlan elaboratedShared
594 return (improvedPlan
, elaboratedPlan
, elaboratedShared
, totalIndexState
, activeRepos
)
596 fileMonitorSolverPlan
= newFileMonitorInCacheDir
"solver-plan"
597 fileMonitorSourceHashes
= newFileMonitorInCacheDir
"source-hashes"
598 fileMonitorElaboratedPlan
= newFileMonitorInCacheDir
"elaborated-plan"
599 fileMonitorImprovedPlan
= newFileMonitorInCacheDir
"improved-plan"
601 newFileMonitorInCacheDir
:: Eq a
=> FilePath -> FileMonitor a b
602 newFileMonitorInCacheDir
= newFileMonitor
. distProjectCacheFile
604 -- Configure the compiler we're using.
606 -- This is moderately expensive and doesn't change that often so we cache
609 phaseConfigureCompiler
611 -> Rebuild
(Compiler
, Platform
, ProgramDb
)
612 phaseConfigureCompiler
= configureCompiler verbosity distDirLayout
614 -- Configuring other programs.
616 -- Having configred the compiler, now we configure all the remaining
617 -- programs. This is to check we can find them, and to monitor them for
620 -- TODO: [required eventually] we don't actually do this yet.
622 -- We rely on the fact that the previous phase added the program config for
623 -- all local packages, but that all the programs configured so far are the
624 -- compiler program or related util programs.
626 phaseConfigurePrograms
628 -> (Compiler
, Platform
, ProgramDb
)
630 phaseConfigurePrograms projectConfig
(_
, _
, compilerprogdb
) = do
631 -- Users are allowed to specify program locations independently for
632 -- each package (e.g. to use a particular version of a pre-processor
633 -- for some packages). However they cannot do this for the compiler
634 -- itself as that's just not going to work. So we check for this.
636 checkBadPerPackageCompilerPaths
637 (configuredPrograms compilerprogdb
)
638 (getMapMappend
(projectConfigSpecificPackage projectConfig
))
640 -- TODO: [required eventually] find/configure other programs that the
643 -- TODO: [required eventually] find/configure all build-tools
644 -- but note that some of them may be built as part of the plan.
646 -- Run the solver to get the initial install plan.
647 -- This is expensive so we cache it independently.
651 -> (Compiler
, Platform
, ProgramDb
)
652 -> [PackageSpecifier UnresolvedSourcePackage
]
653 -> InstalledPackageIndex
654 -> Rebuild
(SolverInstallPlan
, PkgConfigDb
, IndexUtils
.TotalIndexState
, IndexUtils
.ActiveRepos
)
656 projectConfig
@ProjectConfig
657 { projectConfigShared
658 , projectConfigBuildOnly
660 (compiler
, platform
, progdb
)
665 fileMonitorSolverPlan
668 , localPackagesEnabledStanzas
671 , programDbSignature progdb
681 (sourcePkgDb
, tis
, ar
) <-
685 (solverSettingIndexState solverSettings
)
686 (solverSettingActiveRepos solverSettings
)
687 pkgConfigDB
<- getPkgConfigDb verbosity progdb
689 -- TODO: [code cleanup] it'd be better if the Compiler contained the
690 -- ConfiguredPrograms that it needs, rather than relying on the progdb
691 -- since we don't need to depend on all the programs here, just the
692 -- ones relevant for the compiler.
695 notice verbosity
"Resolving dependencies..."
697 foldProgress logMsg
(pure
. Left
) (pure
. Right
) $
703 (installedPackages
<> installedPkgIndex
)
707 localPackagesEnabledStanzas
710 reportPlanningFailure projectConfig compiler platform localPackages
711 dieWithException verbosity
$ PhaseRunSolverErr msg
712 Right plan
-> return (plan
, pkgConfigDB
, tis
, ar
)
714 corePackageDbs
:: [PackageDB
]
718 (projectConfigPackageDBs projectConfigShared
)
720 withRepoCtx
:: (RepoContext
-> IO a
) -> IO a
722 projectConfigWithSolverRepoContext
725 projectConfigBuildOnly
727 solverSettings
= resolveSolverSettings projectConfig
728 logMsg message rest
= debugNoWrap verbosity message
>> rest
730 localPackagesEnabledStanzas
=
733 | pkg
<- localPackages
734 , -- TODO: misnomer: we should separate
735 -- builtin/global/inplace/local packages
736 -- and packages explicitly mentioned in the project
738 let pkgname
= pkgSpecifierTarget pkg
740 lookupLocalPackageConfig
745 lookupLocalPackageConfig
746 packageConfigBenchmarks
749 isLocal
= isJust (shouldBeLocal pkg
)
753 [ (TestStanzas
, enabled
)
754 | enabled
<- flagToList testsEnabled
756 ++ [ (BenchStanzas
, enabled
)
757 | enabled
<- flagToList benchmarksEnabled
759 |
otherwise = Map
.fromList
[(TestStanzas
, False), (BenchStanzas
, False)]
762 -- Elaborate the solver's install plan to get a fully detailed plan. This
763 -- version of the plan has the final nix-style hashed ids.
767 -> (Compiler
, Platform
, ProgramDb
)
770 -> [PackageSpecifier
(SourcePackage
(PackageLocation loc
))]
772 ( ElaboratedInstallPlan
773 , ElaboratedSharedConfig
777 { projectConfigShared
778 , projectConfigAllPackages
779 , projectConfigLocalPackages
780 , projectConfigSpecificPackage
781 , projectConfigBuildOnly
783 (compiler
, platform
, progdb
)
787 liftIO
$ debug verbosity
"Elaborating the install plan..."
789 sourcePackageHashes
<-
792 fileMonitorSourceHashes
793 (packageLocationsSignature solverPlan
)
794 $ getPackageSourceHashes verbosity withRepoCtx solverPlan
796 defaultInstallDirs
<- liftIO
$ userInstallDirTemplates compiler
797 let installDirs
= fmap Cabal
.fromFlag
$ (fmap Flag defaultInstallDirs
) <> (projectConfigInstallDirs projectConfigShared
)
798 (elaboratedPlan
, elaboratedShared
) <-
799 liftIO
. runLogProgress verbosity
$
813 projectConfigAllPackages
814 projectConfigLocalPackages
815 (getMapMappend projectConfigSpecificPackage
)
816 let instantiatedPlan
=
817 instantiateInstallPlan
822 liftIO
$ debugNoWrap verbosity
(showElaboratedInstallPlan instantiatedPlan
)
823 return (instantiatedPlan
, elaboratedShared
)
825 withRepoCtx
:: (RepoContext
-> IO a
) -> IO a
827 projectConfigWithSolverRepoContext
830 projectConfigBuildOnly
832 -- Update the files we maintain that reflect our current build environment.
833 -- In particular we maintain a JSON representation of the elaborated
834 -- install plan (but not the improved plan since that reflects the state
835 -- of the build rather than just the input environment).
837 phaseMaintainPlanOutputs
838 :: ElaboratedInstallPlan
839 -> ElaboratedSharedConfig
841 phaseMaintainPlanOutputs elaboratedPlan elaboratedShared
= liftIO
$ do
842 debug verbosity
"Updating plan.json"
843 writePlanExternalRepresentation
848 -- Improve the elaborated install plan. The elaborated plan consists
849 -- mostly of source packages (with full nix-style hashed ids). Where
850 -- corresponding installed packages already exist in the store, replace
853 -- Note that we do monitor the store's package db here, so we will redo
854 -- this improvement phase when the db changes -- including as a result of
855 -- executing a plan and installing things.
858 :: ElaboratedInstallPlan
859 -> ElaboratedSharedConfig
860 -> Rebuild ElaboratedInstallPlan
861 phaseImprovePlan elaboratedPlan elaboratedShared
= do
862 liftIO
$ debug verbosity
"Improving the install plan..."
863 storePkgIdSet
<- getStoreEntries cabalStoreDirLayout compid
865 improveInstallPlanWithInstalledPackages
868 liftIO
$ debugNoWrap verbosity
(showElaboratedInstallPlan improvedPlan
)
869 -- TODO: [nice to have] having checked which packages from the store
870 -- we're using, it may be sensible to sanity check those packages
871 -- by loading up the compiler package db and checking everything
872 -- matches up as expected, e.g. no dangling deps, files deleted.
875 compid
= compilerId
(pkgConfigCompiler elaboratedShared
)
877 -- | If a 'PackageSpecifier' refers to a single package, return Just that
879 reportPlanningFailure
:: ProjectConfig
-> Compiler
-> Platform
-> [PackageSpecifier UnresolvedSourcePackage
] -> IO ()
880 reportPlanningFailure projectConfig comp platform pkgSpecifiers
=
882 BuildReports
.storeLocal
884 (fromNubList
$ projectConfigSummaryFile
. projectConfigBuildOnly
$ projectConfig
)
888 -- TODO may want to handle the projectConfigLogFile paramenter here, or just remove it entirely?
890 reportFailure
= Cabal
.fromFlag
. projectConfigReportPlanningFailure
. projectConfigBuildOnly
$ projectConfig
891 pkgids
= mapMaybe theSpecifiedPackage pkgSpecifiers
893 BuildReports
.fromPlanningFailure
897 -- TODO we may want to get more flag assignments and merge them here?
898 (packageConfigFlagAssignment
. projectConfigAllPackages
$ projectConfig
)
900 theSpecifiedPackage
:: Package pkg
=> PackageSpecifier pkg
-> Maybe PackageId
901 theSpecifiedPackage pkgSpec
=
903 NamedPackage name
[PackagePropertyVersion version
] ->
904 PackageIdentifier name
<$> trivialRange version
905 NamedPackage _ _
-> Nothing
906 SpecificSourcePackage pkg
-> Just
$ packageId pkg
907 -- \| If a range includes only a single version, return Just that version.
908 trivialRange
:: VersionRange
-> Maybe Version
918 programsMonitorFiles
:: ProgramDb
-> [MonitorFilePath
]
919 programsMonitorFiles progdb
=
921 | prog
<- configuredPrograms progdb
923 monitorFileSearchPath
924 (programMonitorFiles prog
)
928 -- | Select the bits of a 'ProgramDb' to monitor for value changes.
929 -- Use 'programsMonitorFiles' for the files to monitor.
930 programDbSignature
:: ProgramDb
-> [ConfiguredProgram
]
931 programDbSignature progdb
=
933 { programMonitorFiles
= []
934 , programOverrideEnv
=
937 (programOverrideEnv prog
)
939 | prog
<- configuredPrograms progdb
948 -> Rebuild InstalledPackageIndex
949 getInstalledPackages verbosity compiler progdb platform packagedbs
= do
950 monitorFiles
. map monitorFileOrDirectory
952 ( IndexUtils
.getInstalledPackagesMonitorFiles
960 IndexUtils
.getInstalledPackages
967 --TODO: [nice to have] use this but for sanity / consistency checking
968 getPackageDBContents :: Verbosity
969 -> Compiler -> ProgramDb -> Platform
971 -> Rebuild InstalledPackageIndex
972 getPackageDBContents verbosity compiler progdb platform packagedb = do
973 monitorFiles . map monitorFileOrDirectory
974 =<< liftIO (IndexUtils.getInstalledPackagesMonitorFiles
976 [packagedb] progdb platform)
978 createPackageDBIfMissing verbosity compiler progdb packagedb
979 Cabal.getPackageDBContents verbosity compiler
985 -> (forall a
. (RepoContext
-> IO a
) -> IO a
)
986 -> Maybe IndexUtils
.TotalIndexState
987 -> Maybe IndexUtils
.ActiveRepos
988 -> Rebuild
(SourcePackageDb
, IndexUtils
.TotalIndexState
, IndexUtils
.ActiveRepos
)
989 getSourcePackages verbosity withRepoCtx idxState activeRepos
= do
990 (sourcePkgDbWithTIS
, repos
) <-
992 withRepoCtx
$ \repoctx
-> do
993 sourcePkgDbWithTIS
<- IndexUtils
.getSourcePackagesAtIndexState verbosity repoctx idxState activeRepos
994 return (sourcePkgDbWithTIS
, repoContextRepos repoctx
)
996 traverse_ needIfExists
997 . IndexUtils
.getSourcePackagesMonitorFiles
999 return sourcePkgDbWithTIS
1001 getPkgConfigDb
:: Verbosity
-> ProgramDb
-> Rebuild PkgConfigDb
1002 getPkgConfigDb verbosity progdb
= do
1003 dirs
<- liftIO
$ getPkgConfigDbDirs verbosity progdb
1004 -- Just monitor the dirs so we'll notice new .pc files.
1005 -- Alternatively we could monitor all the .pc files too.
1006 traverse_ monitorDirectoryStatus dirs
1007 liftIO
$ readPkgConfigDb verbosity progdb
1009 -- | Select the config values to monitor for changes package source hashes.
1010 packageLocationsSignature
1011 :: SolverInstallPlan
1012 -> [(PackageId
, PackageLocation
(Maybe FilePath))]
1013 packageLocationsSignature solverPlan
=
1014 [ (packageId pkg
, srcpkgSource pkg
)
1015 | SolverInstallPlan
.Configured
(SolverPackage
{solverPkgSource
= pkg
}) <-
1016 SolverInstallPlan
.toList solverPlan
1019 -- | Get the 'HashValue' for all the source packages where we use hashes,
1020 -- and download any packages required to do so.
1022 -- Note that we don't get hashes for local unpacked packages.
1023 getPackageSourceHashes
1025 -> (forall a
. (RepoContext
-> IO a
) -> IO a
)
1026 -> SolverInstallPlan
1027 -> Rebuild
(Map PackageId PackageSourceHash
)
1028 getPackageSourceHashes verbosity withRepoCtx solverPlan
= do
1029 -- Determine if and where to get the package's source hash from.
1031 let allPkgLocations
:: [(PackageId
, PackageLocation
(Maybe FilePath))]
1033 [ (packageId pkg
, srcpkgSource pkg
)
1034 | SolverInstallPlan
.Configured
(SolverPackage
{solverPkgSource
= pkg
}) <-
1035 SolverInstallPlan
.toList solverPlan
1038 -- Tarballs that were local in the first place.
1039 -- We'll hash these tarball files directly.
1040 localTarballPkgs
:: [(PackageId
, FilePath)]
1043 |
(pkgid
, LocalTarballPackage tarball
) <- allPkgLocations
1046 -- Tarballs from remote URLs. We must have downloaded these already
1047 -- (since we extracted the .cabal file earlier)
1050 |
(pkgid
, RemoteTarballPackage _
(Just tarball
)) <- allPkgLocations
1053 -- tarballs from source-repository-package stanzas
1054 sourceRepoTarballPkgs
=
1056 |
(pkgid
, RemoteSourceRepoPackage _
(Just tarball
)) <- allPkgLocations
1059 -- Tarballs from repositories, either where the repository provides
1060 -- hashes as part of the repo metadata, or where we will have to
1061 -- download and hash the tarball.
1062 repoTarballPkgsWithMetadataUnvalidated
:: [(PackageId
, Repo
)]
1063 repoTarballPkgsWithoutMetadata
:: [(PackageId
, Repo
)]
1064 ( repoTarballPkgsWithMetadataUnvalidated
1065 , repoTarballPkgsWithoutMetadata
1069 RepoSecure
{} -> Left
(pkgid
, repo
)
1070 _
-> Right
(pkgid
, repo
)
1071 |
(pkgid
, RepoTarballPackage repo _ _
) <- allPkgLocations
1074 (repoTarballPkgsWithMetadata
, repoTarballPkgsToDownloadWithMeta
) <- fmap partitionEithers
$
1076 withRepoCtx
$ \repoctx
-> forM repoTarballPkgsWithMetadataUnvalidated
$
1078 verifyFetchedTarball verbosity repoctx repo pkg
>>= \b -> case b
of
1079 True -> return $ Left x
1080 False -> return $ Right x
1082 -- For tarballs from repos that do not have hashes available we now have
1083 -- to check if the packages were downloaded already.
1085 ( repoTarballPkgsToDownloadWithNoMeta
1086 , repoTarballPkgsDownloaded
1088 fmap partitionEithers
$
1092 mtarball
<- checkRepoTarballFetched repo pkgid
1094 Nothing
-> return (Left
(pkgid
, repo
))
1095 Just tarball
-> return (Right
(pkgid
, tarball
))
1096 |
(pkgid
, repo
) <- repoTarballPkgsWithoutMetadata
1099 let repoTarballPkgsToDownload
= repoTarballPkgsToDownloadWithMeta
++ repoTarballPkgsToDownloadWithNoMeta
1100 ( hashesFromRepoMetadata
1101 , repoTarballPkgsNewlyDownloaded
1103 -- Avoid having to initialise the repository (ie 'withRepoCtx') if we
1104 -- don't have to. (The main cost is configuring the http client.)
1105 if null repoTarballPkgsToDownload
&& null repoTarballPkgsWithMetadata
1106 then return (Map
.empty, [])
1107 else liftIO
$ withRepoCtx
$ \repoctx
-> do
1108 -- For tarballs from repos that do have hashes available as part of the
1109 -- repo metadata we now load up the index for each repo and retrieve
1110 -- the hashes for the packages
1112 hashesFromRepoMetadata
<-
1113 Sec
.uncheckClientErrors
$ -- TODO: [code cleanup] wrap in our own exceptions
1114 fmap (Map
.fromList
. concat) $
1116 -- Reading the repo index is expensive so we group the packages by repo
1117 [ repoContextWithSecureRepo repoctx repo
$ \secureRepo
->
1118 Sec
.withIndex secureRepo
$ \repoIndex
->
1123 <$> Sec
.indexLookupHash repoIndex pkgid
-- strip off Trusted tag
1125 -- Note that hackage-security currently uses SHA256
1126 -- but this API could in principle give us some other
1127 -- choice in future.
1128 return (pkgid
, hashFromTUF hash
)
1132 map (\grp
@((_
, repo
) :| _
) -> (repo
, map fst (NE
.toList grp
)))
1133 . NE
.groupBy ((==) `on`
(remoteRepoName
. repoRemote
. snd))
1134 . sortBy (compare `on`
(remoteRepoName
. repoRemote
. snd))
1135 $ repoTarballPkgsWithMetadata
1138 -- For tarballs from repos that do not have hashes available, download
1139 -- the ones we previously determined we need.
1141 repoTarballPkgsNewlyDownloaded
<-
1144 tarball
<- fetchRepoTarball verbosity repoctx repo pkgid
1145 return (pkgid
, tarball
)
1146 |
(pkgid
, repo
) <- repoTarballPkgsToDownload
1150 ( hashesFromRepoMetadata
1151 , repoTarballPkgsNewlyDownloaded
1154 -- Hash tarball files for packages where we have to do that. This includes
1155 -- tarballs that were local in the first place, plus tarballs from repos,
1156 -- either previously cached or freshly downloaded.
1158 let allTarballFilePkgs
:: [(PackageId
, FilePath)]
1159 allTarballFilePkgs
=
1161 ++ remoteTarballPkgs
1162 ++ sourceRepoTarballPkgs
1163 ++ repoTarballPkgsDownloaded
1164 ++ repoTarballPkgsNewlyDownloaded
1165 hashesFromTarballFiles
<-
1170 srchash
<- readFileHashValue tarball
1171 return (pkgid
, srchash
)
1172 |
(pkgid
, tarball
) <- allTarballFilePkgs
1175 [ monitorFile tarball
1176 |
(_pkgid
, tarball
) <- allTarballFilePkgs
1179 -- Return the combination
1181 hashesFromRepoMetadata
1182 <> hashesFromTarballFiles
1184 -- | Append the given package databases to an existing PackageDBStack.
1185 -- A @Nothing@ entry will clear everything before it.
1186 applyPackageDbFlags
:: PackageDBStack
-> [Maybe PackageDB
] -> PackageDBStack
1187 applyPackageDbFlags dbs
' [] = dbs
'
1188 applyPackageDbFlags _
(Nothing
: dbs
) = applyPackageDbFlags
[] dbs
1189 applyPackageDbFlags dbs
' (Just db
: dbs
) = applyPackageDbFlags
(dbs
' ++ [db
]) dbs
1191 -- ------------------------------------------------------------
1193 -- * Installation planning
1195 -- ------------------------------------------------------------
1202 -> InstalledPackageIndex
1205 -> [PackageSpecifier UnresolvedSourcePackage
]
1206 -> Map PackageName
(Map OptionalStanza
Bool)
1207 -> Progress
String String SolverInstallPlan
1224 -- TODO: [nice to have] disable multiple instances restriction in
1225 -- the solver, but then make sure we can cope with that in the
1227 resolverParams
:: DepResolverParams
1229 setMaxBackjumps solverSettingMaxBackjumps
1230 . setIndependentGoals solverSettingIndependentGoals
1231 . setReorderGoals solverSettingReorderGoals
1232 . setCountConflicts solverSettingCountConflicts
1233 . setFineGrainedConflicts solverSettingFineGrainedConflicts
1234 . setMinimizeConflictSet solverSettingMinimizeConflictSet
1235 -- TODO: [required eventually] should only be configurable for
1237 -- . setAvoidReinstalls solverSettingAvoidReinstalls
1239 -- TODO: [required eventually] should only be configurable for
1241 -- . setShadowPkgs solverSettingShadowPkgs
1243 . setStrongFlags solverSettingStrongFlags
1244 . setAllowBootLibInstalls solverSettingAllowBootLibInstalls
1245 . setOnlyConstrained solverSettingOnlyConstrained
1246 . setSolverVerbosity verbosity
1247 -- TODO: [required eventually] decide if we need to prefer
1248 -- installed for global packages, or prefer latest even for
1249 -- global packages. Perhaps should be configurable but with a
1250 -- different name than "upgrade-dependencies".
1251 . setPreferenceDefault
1252 ( if Cabal
.asBool solverSettingPreferOldest
1253 then PreferAllOldest
1254 else PreferLatestForSelected
1256 {-(if solverSettingUpgradeDeps
1257 then PreferAllLatest
1258 else PreferLatestForSelected)-}
1260 . removeLowerBounds solverSettingAllowOlder
1261 . removeUpperBounds solverSettingAllowNewer
1262 . addDefaultSetupDependencies
1263 ( mkDefaultSetupDeps comp platform
1264 . PD
.packageDescription
1267 . addSetupCabalMinVersionConstraint setupMinCabalVersionConstraint
1268 . addSetupCabalMaxVersionConstraint setupMaxCabalVersionConstraint
1270 -- preferences from the config file or command line
1271 [ PackageVersionPreference name ver
1272 | PackageVersionConstraint name ver
<- solverSettingPreferences
1275 -- version constraints from the config file or command line
1276 [ LabeledPackageConstraint
(userToPackageConstraint pc
) src
1277 |
(pc
, src
) <- solverSettingConstraints
1280 -- enable stanza preference unilaterally, regardless if the user asked
1281 -- accordingly or expressed no preference, to help hint the solver
1282 [ PackageStanzasPreference pkgname stanzas
1283 | pkg
<- localPackages
1284 , let pkgname
= pkgSpecifierTarget pkg
1285 stanzaM
= Map
.findWithDefault Map
.empty pkgname pkgStanzasEnable
1287 [ stanza | stanza
<- [minBound .. maxBound], Map
.lookup stanza stanzaM
/= Just
False
1289 , not (null stanzas
)
1292 -- enable stanza constraints where the user asked to enable
1293 [ LabeledPackageConstraint
1295 (scopeToplevel pkgname
)
1296 (PackagePropertyStanzas stanzas
)
1298 ConstraintSourceConfigFlagOrTarget
1299 | pkg
<- localPackages
1300 , let pkgname
= pkgSpecifierTarget pkg
1301 stanzaM
= Map
.findWithDefault Map
.empty pkgname pkgStanzasEnable
1303 [ stanza | stanza
<- [minBound .. maxBound], Map
.lookup stanza stanzaM
== Just
True
1305 , not (null stanzas
)
1308 -- TODO: [nice to have] should have checked at some point that the
1309 -- package in question actually has these flags.
1310 [ LabeledPackageConstraint
1312 (scopeToplevel pkgname
)
1313 (PackagePropertyFlags flags
)
1315 ConstraintSourceConfigFlagOrTarget
1316 |
(pkgname
, flags
) <- Map
.toList solverSettingFlagAssignments
1319 -- TODO: [nice to have] we have user-supplied flags for unspecified
1320 -- local packages (as well as specific per-package flags). For the
1321 -- former we just apply all these flags to all local targets which
1322 -- is silly. We should check if the flags are appropriate.
1323 [ LabeledPackageConstraint
1325 (scopeToplevel pkgname
)
1326 (PackagePropertyFlags flags
)
1328 ConstraintSourceConfigFlagOrTarget
1329 |
let flags
= solverSettingFlagAssignment
1330 , not (PD
.nullFlagAssignment flags
)
1331 , pkg
<- localPackages
1332 , let pkgname
= pkgSpecifierTarget pkg
1336 stdResolverParams
:: DepResolverParams
1338 -- Note: we don't use the standardInstallPolicy here, since that uses
1339 -- its own addDefaultSetupDependencies that is not appropriate for us.
1345 -- While we can talk to older Cabal versions (we need to be able to
1346 -- do so for custom Setup scripts that require older Cabal lib
1347 -- versions), we have problems talking to some older versions that
1348 -- don't support certain features.
1350 -- For example, Cabal-1.16 and older do not know about build targets.
1351 -- Even worse, 1.18 and older only supported the --constraint flag
1352 -- with source package ids, not --dependency with installed package
1353 -- ids. That is bad because we cannot reliably select the right
1354 -- dependencies in the presence of multiple instances (i.e. the
1355 -- store). See issue #3932. So we require Cabal 1.20 as a minimum.
1357 -- Moreover, lib:Cabal generally only supports the interface of
1358 -- current and past compilers; in fact recent lib:Cabal versions
1359 -- will warn when they encounter a too new or unknown GHC compiler
1360 -- version (c.f. #415). To avoid running into unsupported
1361 -- configurations we encode the compatibility matrix as lower
1362 -- bounds on lib:Cabal here (effectively corresponding to the
1363 -- respective major Cabal version bundled with the respective GHC
1366 -- GHC 9.2 needs Cabal >= 3.6
1367 -- GHC 9.0 needs Cabal >= 3.4
1368 -- GHC 8.10 needs Cabal >= 3.2
1369 -- GHC 8.8 needs Cabal >= 3.0
1370 -- GHC 8.6 needs Cabal >= 2.4
1371 -- GHC 8.4 needs Cabal >= 2.2
1372 -- GHC 8.2 needs Cabal >= 2.0
1373 -- GHC 8.0 needs Cabal >= 1.24
1374 -- GHC 7.10 needs Cabal >= 1.22
1376 -- (NB: we don't need to consider older GHCs as Cabal >= 1.20 is
1377 -- the absolute lower bound)
1379 -- TODO: long-term, this compatibility matrix should be
1380 -- stored as a field inside 'Distribution.Compiler.Compiler'
1381 setupMinCabalVersionConstraint
1382 | isGHC
, compVer
>= mkVersion
[9, 6] = mkVersion
[3, 10]
1383 | isGHC
, compVer
>= mkVersion
[9, 4] = mkVersion
[3, 8]
1384 | isGHC
, compVer
>= mkVersion
[9, 2] = mkVersion
[3, 6]
1385 | isGHC
, compVer
>= mkVersion
[9, 0] = mkVersion
[3, 4]
1386 | isGHC
, compVer
>= mkVersion
[8, 10] = mkVersion
[3, 2]
1387 | isGHC
, compVer
>= mkVersion
[8, 8] = mkVersion
[3, 0]
1388 | isGHC
, compVer
>= mkVersion
[8, 6] = mkVersion
[2, 4]
1389 | isGHC
, compVer
>= mkVersion
[8, 4] = mkVersion
[2, 2]
1390 | isGHC
, compVer
>= mkVersion
[8, 2] = mkVersion
[2, 0]
1391 | isGHC
, compVer
>= mkVersion
[8, 0] = mkVersion
[1, 24]
1392 | isGHC
, compVer
>= mkVersion
[7, 10] = mkVersion
[1, 22]
1393 |
otherwise = mkVersion
[1, 20]
1395 isGHC
= compFlav `
elem`
[GHC
, GHCJS
]
1396 compFlav
= compilerFlavor comp
1397 compVer
= compilerVersion comp
1399 -- As we can't predict the future, we also place a global upper
1400 -- bound on the lib:Cabal version we know how to interact with:
1402 -- The upper bound is computed by incrementing the current major
1403 -- version twice in order to allow for the current version, as
1404 -- well as the next adjacent major version (one of which will not
1405 -- be released, as only "even major" versions of Cabal are
1406 -- released to Hackage or bundled with proper GHC releases).
1408 -- For instance, if the current version of cabal-install is an odd
1409 -- development version, e.g. Cabal-2.1.0.0, then we impose an
1410 -- upper bound `setup.Cabal < 2.3`; if `cabal-install` is on a
1411 -- stable/release even version, e.g. Cabal-2.2.1.0, the upper
1412 -- bound is `setup.Cabal < 2.4`. This gives us enough flexibility
1413 -- when dealing with development snapshots of Cabal and cabal-install.
1415 setupMaxCabalVersionConstraint
=
1416 alterVersion
(take 2) $ incVersion
1 $ incVersion
1 cabalVersion
1418 ------------------------------------------------------------------------------
1420 -- * Install plan post-processing
1422 ------------------------------------------------------------------------------
1424 -- This phase goes from the InstallPlan we get from the solver and has to
1425 -- make an elaborated install plan.
1427 -- We go in two steps:
1429 -- 1. elaborate all the source packages that the solver has chosen.
1430 -- 2. swap source packages for pre-existing installed packages wherever
1433 -- We do it in this order, elaborating and then replacing, because the easiest
1434 -- way to calculate the installed package ids used for the replacement step is
1435 -- from the elaborated configuration for each package.
1437 ------------------------------------------------------------------------------
1439 -- * Install plan elaboration
1441 ------------------------------------------------------------------------------
1443 -- Note [SolverId to ConfiguredId]
1444 -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
1445 -- Dependency solving is a per package affair, so after we're done, we
1446 -- end up with 'SolverInstallPlan' that records in 'solverPkgLibDeps'
1447 -- and 'solverPkgExeDeps' what packages provide the libraries and executables
1448 -- needed by each component of the package (phew!) For example, if I have
1451 -- build-depends: lib
1452 -- build-tool-depends: pkg:exe1
1453 -- build-tools: alex
1455 -- After dependency solving, I find out that this library component has
1456 -- library dependencies on lib-0.2, and executable dependencies on pkg-0.1
1457 -- and alex-0.3 (other components of the package may have different
1458 -- dependencies). Note that I've "lost" the knowledge that I depend
1460 -- * specifically* on the exe1 executable from pkg.
1463 -- So, we have a this graph of packages, and we need to transform it into
1464 -- a graph of components which we are actually going to build. In particular:
1466 -- NODE changes from PACKAGE (SolverPackage) to COMPONENTS (ElaboratedConfiguredPackage)
1467 -- EDGE changes from PACKAGE DEP (SolverId) to COMPONENT DEPS (ConfiguredId)
1469 -- In both cases, what was previously a single node/edge may turn into multiple
1470 -- nodes/edges. Multiple components, because there may be multiple components
1471 -- in a package; multiple component deps, because we may depend upon multiple
1472 -- executables from the same package (and maybe, some day, multiple libraries
1473 -- from the same package.)
1475 -- Let's talk about how to do this transformation. Naively, we might consider
1476 -- just processing each package, converting it into (zero or) one or more
1477 -- components. But we also have to update the edges; this leads to
1478 -- two complications:
1480 -- 1. We don't know what the ConfiguredId of a component is until
1481 -- we've configured it, but we cannot configure a component unless
1482 -- we know the ConfiguredId of all its dependencies. Thus, we must
1483 -- process the 'SolverInstallPlan' in topological order.
1485 -- 2. When we process a package, we know the SolverIds of its
1486 -- dependencies, but we have to do some work to turn these into
1487 -- ConfiguredIds. For example, in the case of build-tool-depends, the
1488 -- SolverId isn't enough to uniquely determine the ConfiguredId we should
1489 -- elaborate to: we have to look at the executable name attached to
1490 -- the package name in the package description to figure it out.
1491 -- At the same time, we NEED to use the SolverId, because there might
1492 -- be multiple versions of the same package in the build plan
1493 -- (due to setup dependencies); we can't just look up the package name
1494 -- from the package description.
1496 -- We can adopt the following strategy:
1498 -- * When a package is transformed into components, record
1499 -- a mapping from SolverId to ALL of the components
1500 -- which were elaborated.
1502 -- * When we look up an edge, we use our knowledge of the
1503 -- component name to *filter* the list of components into
1504 -- the ones we actually wanted to refer to.
1506 -- By the way, we can tell that SolverInstallPlan is not the "right" type
1507 -- because a SolverId cannot adequately represent all possible dependency
1508 -- solver states: we may need to record foo-0.1 multiple times in
1509 -- the solver install plan with different dependencies. This imprecision in the
1510 -- type currently doesn't cause any problems because the dependency solver
1511 -- continues to enforce the single instance restriction regardless of compiler
1512 -- version. The right way to solve this is to come up with something very much
1513 -- like a 'ConfiguredId', in that it incorporates the version choices of its
1514 -- dependencies, but less fine grained.
1516 -- | Produce an elaborated install plan using the policy for local builds with
1517 -- a nix-style shared store.
1519 -- In theory should be able to make an elaborated install plan with a policy
1520 -- matching that of the classic @cabal install --user@ or @--global@
1521 elaborateInstallPlan
1529 -> SolverInstallPlan
1530 -> [PackageSpecifier
(SourcePackage
(PackageLocation loc
))]
1531 -> Map PackageId PackageSourceHash
1532 -> InstallDirs
.InstallDirTemplates
1533 -> ProjectConfigShared
1536 -> Map PackageName PackageConfig
1537 -> LogProgress
(ElaboratedInstallPlan
, ElaboratedSharedConfig
)
1538 elaborateInstallPlan
1544 distDirLayout
@DistDirLayout
{..}
1545 storeDirLayout
@StoreDirLayout
{storePackageDBStack
}
1553 perPackageConfig
= do
1554 x
<- elaboratedInstallPlan
1555 return (x
, elaboratedSharedConfig
)
1557 elaboratedSharedConfig
=
1558 ElaboratedSharedConfig
1559 { pkgConfigPlatform
= platform
1560 , pkgConfigCompiler
= compiler
1561 , pkgConfigCompilerProgs
= compilerprogdb
1562 , pkgConfigReplOptions
= mempty
1565 preexistingInstantiatedPkgs
:: Map UnitId FullUnitId
1566 preexistingInstantiatedPkgs
=
1567 Map
.fromList
(mapMaybe f
(SolverInstallPlan
.toList solverPlan
))
1569 f
(SolverInstallPlan
.PreExisting inst
)
1570 |
let ipkg
= instSolverPkgIPI inst
1571 , not (IPI
.indefinite ipkg
) =
1573 ( IPI
.installedUnitId ipkg
1575 (IPI
.installedComponentId ipkg
)
1576 (Map
.fromList
(IPI
.instantiatedWith ipkg
))
1581 elaboratedInstallPlan
1582 :: LogProgress
(InstallPlan
.GenericInstallPlan IPI
.InstalledPackageInfo ElaboratedConfiguredPackage
)
1583 elaboratedInstallPlan
=
1584 flip InstallPlan
.fromSolverInstallPlanWithProgress solverPlan
$ \mapDep planpkg
->
1586 SolverInstallPlan
.PreExisting pkg
->
1587 return [InstallPlan
.PreExisting
(instSolverPkgIPI pkg
)]
1588 SolverInstallPlan
.Configured pkg
->
1590 | shouldBuildInplaceOnly pkg
= text
"inplace"
1591 |
otherwise = Disp
.empty
1596 <+> quotes
(pretty
(packageId pkg
))
1598 $ map InstallPlan
.Configured
<$> elaborateSolverToComponents mapDep pkg
1600 -- NB: We don't INSTANTIATE packages at this point. That's
1601 -- a post-pass. This makes it simpler to compute dependencies.
1602 elaborateSolverToComponents
1603 :: (SolverId
-> [ElaboratedPlanPackage
])
1604 -> SolverPackage UnresolvedPkgLoc
1605 -> LogProgress
[ElaboratedConfiguredPackage
]
1606 elaborateSolverToComponents mapDep spkg
@(SolverPackage _ _ _ deps0 exe_deps0
) =
1607 case mkComponentsGraph
(elabEnabledSpec elab0
) pd
of
1609 let src_comps
= componentsGraphToList g
1612 (text
"Component graph for" <+> pretty pkgid
<<>> colon
)
1614 (dispComponentsWithDeps src_comps
)
1618 (Map
.empty, Map
.empty, Map
.empty)
1620 let not_per_component_reasons
= why_not_per_component src_comps
1621 if null not_per_component_reasons
1624 checkPerPackageOk comps not_per_component_reasons
1626 [ elaborateSolverToPackage spkg g
$
1627 comps
++ maybeToList setupComponent
1632 (text
"Dependency cycle between the following components:")
1634 (vcat
(map (text
. componentNameStanza
) cns
))
1636 -- You are eligible to per-component build if this list is empty
1637 why_not_per_component g
=
1638 cuz_buildtype
++ cuz_spec
++ cuz_length
++ cuz_flag
1640 cuz reason
= [text reason
]
1641 -- We have to disable per-component for now with
1642 -- Configure-type scripts in order to prevent parallel
1643 -- invocation of the same `./configure` script.
1644 -- See https://github.com/haskell/cabal/issues/4548
1646 -- Moreover, at this point in time, only non-Custom setup scripts
1647 -- are supported. Implementing per-component builds with
1648 -- Custom would require us to create a new 'ElabSetup'
1649 -- type, and teach all of the code paths how to handle it.
1650 -- Once you've implemented this, swap it for the code below.
1652 case PD
.buildType
(elabPkgDescription elab0
) of
1653 PD
.Configure
-> cuz
"build-type is Configure"
1654 PD
.Custom
-> cuz
"build-type is Custom"
1656 -- cabal-format versions prior to 1.8 have different build-depends semantics
1657 -- for now it's easier to just fallback to legacy-mode when specVersion < 1.8
1658 -- see, https://github.com/haskell/cabal/issues/4121
1660 | PD
.specVersion pd
>= CabalSpecV1_8
= []
1661 |
otherwise = cuz
"cabal-version is less than 1.8"
1662 -- In the odd corner case that a package has no components at all
1663 -- then keep it as a whole package, since otherwise it turns into
1664 -- 0 component graph nodes and effectively vanishes. We want to
1665 -- keep it around at least for error reporting purposes.
1668 |
otherwise = cuz
"there are no buildable components"
1669 -- For ease of testing, we let per-component builds be toggled
1672 | fromFlagOrDefault
True (projectConfigPerComponent sharedPackageConfig
) =
1674 |
otherwise = cuz
"you passed --disable-per-component"
1676 -- \| Sometimes a package may make use of features which are only
1677 -- supported in per-package mode. If this is the case, we should
1678 -- give an error when this occurs.
1679 checkPerPackageOk comps reasons
= do
1680 let is_sublib
(CLibName
(LSubLibName _
)) = True
1682 when (any (matchElabPkg is_sublib
) comps
) $
1684 text
"Internal libraries only supported with per-component builds."
1685 $$ text
"Per-component builds were disabled because"
1686 <+> fsep
(punctuate comma reasons
)
1687 -- TODO: Maybe exclude Backpack too
1689 elab0
= elaborateSolverToCommon spkg
1690 pkgid
= elabPkgSourceId elab0
1691 pd
= elabPkgDescription elab0
1693 -- TODO: This is just a skeleton to get elaborateSolverToPackage
1694 -- working correctly
1695 -- TODO: When we actually support building these components, we
1696 -- have to add dependencies on this from all other components
1697 setupComponent
:: Maybe ElaboratedConfiguredPackage
1699 | PD
.buildType
(elabPkgDescription elab0
) == PD
.Custom
=
1702 { elabModuleShape
= emptyModuleShape
1703 , elabUnitId
= notImpl
"elabUnitId"
1704 , elabComponentId
= notImpl
"elabComponentId"
1705 , elabLinkedInstantiatedWith
= Map
.empty
1706 , elabInstallDirs
= notImpl
"elabInstallDirs"
1707 , elabPkgOrComp
= ElabComponent
(ElaboratedComponent
{..})
1712 compSolverName
= CD
.ComponentSetup
1713 compComponentName
= Nothing
1715 dep_pkgs
= elaborateLibSolverId mapDep
=<< CD
.setupDeps deps0
1717 compLibDependencies
=
1718 -- MP: No idea what this function does
1719 map (\cid
-> (configuredId cid
, False)) dep_pkgs
1720 compLinkedLibDependencies
= notImpl
"compLinkedLibDependencies"
1721 compOrderLibDependencies
= notImpl
"compOrderLibDependencies"
1724 compExeDependencies
:: [a
]
1725 compExeDependencies
= []
1727 compExeDependencyPaths
:: [a
]
1728 compExeDependencyPaths
= []
1730 compPkgConfigDependencies
:: [a
]
1731 compPkgConfigDependencies
= []
1735 "Distribution.Client.ProjectPlanning.setupComponent: "
1737 ++ " not implemented yet"
1740 :: ( ConfiguredComponentMap
1741 , LinkedComponentMap
1742 , Map ComponentId
FilePath
1746 ( ( ConfiguredComponentMap
1747 , LinkedComponentMap
1748 , Map ComponentId
FilePath
1750 , ElaboratedConfiguredPackage
1752 buildComponent
(cc_map
, lc_map
, exe_map
) comp
=
1754 ( text
"In the stanza"
1755 <+> quotes
(text
(componentNameStanza cname
))
1758 -- 1. Configure the component, but with a place holder ComponentId.
1760 toConfiguredComponent
1762 (error "Distribution.Client.ProjectPlanning.cc_cid: filled in later")
1763 (Map
.unionWith Map
.union external_lib_cc_map cc_map
)
1764 (Map
.unionWith Map
.union external_exe_cc_map cc_map
)
1768 let cid
' = annotatedIdToConfiguredId
. ci_ann_id
$ cid
1769 in (cid
', False) -- filled in later in pruneInstallPlanPhase2)
1770 -- 2. Read out the dependencies from the ConfiguredComponent cc0
1771 let compLibDependencies
=
1772 -- Nub because includes can show up multiple times
1778 compExeDependencies
=
1780 annotatedIdToConfiguredId
1782 compExeDependencyPaths
=
1783 [ (annotatedIdToConfiguredId aid
', path
)
1784 | aid
' <- cc_exe_deps cc0
1785 , Just paths
<- [Map
.lookup (ann_id aid
') exe_map1
]
1788 elab_comp
= ElaboratedComponent
{..}
1790 -- 3. Construct a preliminary ElaboratedConfiguredPackage,
1791 -- and use this to compute the component ID. Fix up cc_id
1795 { elabPkgOrComp
= ElabComponent
$ elab_comp
1797 cid
= case elabBuildStyle elab0
of
1798 BuildInplaceOnly
{} ->
1802 ++ ( case Cabal
.componentNameString cname
of
1804 Just s
-> "-" ++ prettyShow s
1807 hashedInstalledPackageId
1809 elaboratedSharedConfig
1812 cc
= cc0
{cc_ann_id
= fmap (const cid
) (cc_ann_id cc0
)}
1813 infoProgress
$ dispConfiguredComponent cc
1815 -- 4. Perform mix-in linking
1816 let lookup_uid def_uid
=
1817 case Map
.lookup (unDefUnitId def_uid
) preexistingInstantiatedPkgs
of
1819 Nothing
-> error ("lookup_uid: " ++ prettyShow def_uid
)
1825 (elabPkgSourceId elab0
)
1826 (Map
.union external_lc_map lc_map
)
1828 infoProgress
$ dispLinkedComponent lc
1829 -- NB: elab is setup to be the correct form for an
1830 -- indefinite library, or a definite library with no holes.
1831 -- We will modify it in 'instantiateInstallPlan' to handle
1832 -- instantiated packages.
1834 -- 5. Construct the final ElaboratedConfiguredPackage
1838 { elabModuleShape
= lc_shape lc
1839 , elabUnitId
= abstractUnitId
(lc_uid lc
)
1840 , elabComponentId
= lc_cid lc
1841 , elabLinkedInstantiatedWith
= Map
.fromList
(lc_insts lc
)
1845 { compLinkedLibDependencies
= ordNub
(map ci_id
(lc_includes lc
))
1846 , compOrderLibDependencies
=
1849 (abstractUnitId
. ci_id
)
1850 (lc_includes lc
++ lc_sig_includes lc
)
1860 elaboratedSharedConfig
1864 -- 6. Construct the updated local maps
1865 let cc_map
' = extendConfiguredComponentMap cc cc_map
1866 lc_map
' = extendLinkedComponentMap lc lc_map
1867 exe_map
' = Map
.insert cid
(inplace_bin_dir elab
) exe_map
1869 return ((cc_map
', lc_map
', exe_map
'), elab
)
1871 compLinkedLibDependencies
= error "buildComponent: compLinkedLibDependencies"
1872 compOrderLibDependencies
= error "buildComponent: compOrderLibDependencies"
1874 cname
= Cabal
.componentName comp
1875 compComponentName
= Just cname
1876 compSolverName
= CD
.componentNameToComponent cname
1878 -- NB: compLinkedLibDependencies and
1879 -- compOrderLibDependencies are defined when we define
1881 external_lib_dep_sids
= CD
.select
(== compSolverName
) deps0
1882 external_exe_dep_sids
= CD
.select
(== compSolverName
) exe_deps0
1884 external_lib_dep_pkgs
= concatMap mapDep external_lib_dep_sids
1886 -- Combine library and build-tool dependencies, for backwards
1887 -- compatibility (See issue #5412 and the documentation for
1888 -- InstallPlan.fromSolverInstallPlan), but prefer the versions
1889 -- specified as build-tools.
1890 external_exe_dep_pkgs
=
1892 ordNubBy
(pkgName
. packageId
) $
1893 external_exe_dep_sids
++ external_lib_dep_sids
1897 [ (getComponentId pkg
, paths
)
1898 | pkg
<- external_exe_dep_pkgs
1899 , let paths
= planPackageExePaths pkg
1901 exe_map1
= Map
.union external_exe_map
$ fmap (\x
-> [x
]) exe_map
1903 external_lib_cc_map
=
1904 Map
.fromListWith Map
.union $
1905 map mkCCMapping external_lib_dep_pkgs
1906 external_exe_cc_map
=
1907 Map
.fromListWith Map
.union $
1908 map mkCCMapping external_exe_dep_pkgs
1911 map mkShapeMapping
$
1912 external_lib_dep_pkgs
++ concatMap mapDep external_exe_dep_sids
1914 compPkgConfigDependencies
=
1918 "compPkgConfigDependencies: impossible! "
1921 ++ prettyShow
(elabPkgSourceId elab0
)
1923 (pkgConfigDbPkgVersion pkgConfigDB pn
)
1925 | PkgconfigDependency pn _
<-
1927 (Cabal
.componentBuildInfo comp
)
1930 inplace_bin_dir elab
=
1933 elaboratedSharedConfig
1935 $ case Cabal
.componentNameString cname
of
1936 Just n
-> prettyShow n
1939 -- \| Given a 'SolverId' referencing a dependency on a library, return
1940 -- the 'ElaboratedPlanPackage' corresponding to the library. This
1941 -- returns at most one result.
1942 elaborateLibSolverId
1943 :: (SolverId
-> [ElaboratedPlanPackage
])
1945 -> [ElaboratedPlanPackage
]
1946 elaborateLibSolverId mapDep
= filter (matchPlanPkg
(== (CLibName LMainLibName
))) . mapDep
1948 -- \| Given an 'ElaboratedPlanPackage', return the paths to where the
1949 -- executables that this package represents would be installed.
1950 -- The only case where multiple paths can be returned is the inplace
1951 -- monolithic package one, since there can be multiple exes and each one
1952 -- has its own directory.
1953 planPackageExePaths
:: ElaboratedPlanPackage
-> [FilePath]
1954 planPackageExePaths
=
1955 -- Pre-existing executables are assumed to be in PATH
1956 -- already. In fact, this should be impossible.
1957 InstallPlan
.foldPlanPackage
(const []) $ \elab
->
1959 executables
:: [FilePath]
1961 case elabPkgOrComp elab
of
1962 -- Monolithic mode: all exes of the package
1964 unUnqualComponentName
. PD
.exeName
1965 <$> PD
.executables
(elabPkgDescription elab
)
1966 -- Per-component mode: just the selected exe
1967 ElabComponent comp
->
1969 Cabal
.componentNameString
1970 (compComponentName comp
) of
1971 Just
(Just n
) -> [prettyShow n
]
1976 elaboratedSharedConfig
1980 elaborateSolverToPackage
1981 :: SolverPackage UnresolvedPkgLoc
1983 -> [ElaboratedConfiguredPackage
]
1984 -> ElaboratedConfiguredPackage
1985 elaborateSolverToPackage
1987 (SourcePackage pkgid _gpd _srcloc _descOverride
)
1995 -- Knot tying: the final elab includes the
1996 -- pkgInstalledId, which is calculated by hashing many
1997 -- of the other fields of the elaboratedPackage.
2000 elab0
@ElaboratedConfiguredPackage
{..} =
2001 elaborateSolverToCommon pkg
2005 { elabUnitId
= newSimpleUnitId pkgInstalledId
2006 , elabComponentId
= pkgInstalledId
2007 , elabLinkedInstantiatedWith
= Map
.empty
2008 , elabPkgOrComp
= ElabPackage
$ ElaboratedPackage
{..}
2009 , elabModuleShape
= modShape
2018 elaboratedSharedConfig
2022 modShape
= case find (matchElabPkg
(== (CLibName LMainLibName
))) comps
of
2023 Nothing
-> emptyModuleShape
2024 Just e
-> Ty
.elabModuleShape e
2027 | shouldBuildInplaceOnly pkg
=
2028 mkComponentId
(prettyShow pkgid
++ "-inplace")
2030 assert
(isJust elabPkgSourceHash
) $
2031 hashedInstalledPackageId
2033 elaboratedSharedConfig
2034 elab
-- recursive use of elab
2037 -- Need to filter out internal dependencies, because they don't
2038 -- correspond to anything real anymore.
2039 isExt confid
= confSrcId confid
/= pkgid
2040 filterExt
= filter isExt
2042 filterExt
' :: [(ConfiguredId
, a
)] -> [(ConfiguredId
, a
)]
2043 filterExt
' = filter (isExt
. fst)
2045 pkgLibDependencies
=
2046 buildComponentDeps
(filterExt
' . compLibDependencies
)
2047 pkgExeDependencies
=
2048 buildComponentDeps
(filterExt
. compExeDependencies
)
2049 pkgExeDependencyPaths
=
2050 buildComponentDeps
(filterExt
' . compExeDependencyPaths
)
2052 -- TODO: Why is this flat?
2053 pkgPkgConfigDependencies
=
2054 CD
.flatDeps
$ buildComponentDeps compPkgConfigDependencies
2056 pkgDependsOnSelfLib
=
2058 [ (CD
.componentNameToComponent cn
, [()])
2059 | Graph
.N _ cn _
<- fromMaybe [] mb_closure
2062 mb_closure
= Graph
.revClosure compGraph
[k | k
<- Graph
.keys compGraph
, is_lib k
]
2063 -- NB: the sublib case should not occur, because sub-libraries
2064 -- are not supported without per-component builds
2065 is_lib
(CLibName _
) = True
2068 buildComponentDeps
:: Monoid a
=> (ElaboratedComponent
-> a
) -> CD
.ComponentDeps a
2069 buildComponentDeps f
=
2071 [ (compSolverName comp
, f comp
)
2072 | ElaboratedConfiguredPackage
{elabPkgOrComp
= ElabComponent comp
} <- comps
2075 -- NB: This is not the final setting of 'pkgStanzasEnabled'.
2076 -- See [Sticky enabled testsuites]; we may enable some extra
2077 -- stanzas opportunistically when it is cheap to do so.
2079 -- However, we start off by enabling everything that was
2080 -- requested, so that we can maintain an invariant that
2081 -- pkgStanzasEnabled is a superset of elabStanzasRequested
2082 pkgStanzasEnabled
= optStanzaKeysFilteredByValue
(fromMaybe False) elabStanzasRequested
2084 elaborateSolverToCommon
2085 :: SolverPackage UnresolvedPkgLoc
2086 -> ElaboratedConfiguredPackage
2087 elaborateSolverToCommon
2089 (SourcePackage pkgid gdesc srcloc descOverride
)
2097 elaboratedPackage
= ElaboratedConfiguredPackage
{..}
2099 -- These get filled in later
2100 elabUnitId
= error "elaborateSolverToCommon: elabUnitId"
2101 elabComponentId
= error "elaborateSolverToCommon: elabComponentId"
2102 elabInstantiatedWith
= Map
.empty
2103 elabLinkedInstantiatedWith
= error "elaborateSolverToCommon: elabLinkedInstantiatedWith"
2104 elabPkgOrComp
= error "elaborateSolverToCommon: elabPkgOrComp"
2105 elabInstallDirs
= error "elaborateSolverToCommon: elabInstallDirs"
2106 elabModuleShape
= error "elaborateSolverToCommon: elabModuleShape"
2108 elabIsCanonical
= True
2109 elabPkgSourceId
= pkgid
2110 elabPkgDescription
= case PD
.finalizePD
2115 (compilerInfo compiler
)
2118 Right
(desc
, _
) -> desc
2119 Left _
-> error "Failed to finalizePD in elaborateSolverToCommon"
2120 elabFlagAssignment
= flags
2123 [ (PD
.flagName flag
, PD
.flagDefault flag
)
2124 | flag
<- PD
.genPackageFlags gdesc
2127 elabEnabledSpec
= enableStanzas stanzas
2128 elabStanzasAvailable
= stanzas
2130 elabStanzasRequested
:: OptionalStanzaMap
(Maybe Bool)
2131 elabStanzasRequested
= optStanzaTabulate
$ \o
-> case o
of
2132 -- NB: even if a package stanza is requested, if the package
2133 -- doesn't actually have any of that stanza we omit it from
2134 -- the request, to ensure that we don't decide that this
2135 -- package needs to be rebuilt. (It needs to be done here,
2136 -- because the ElaboratedConfiguredPackage is where we test
2137 -- whether or not there have been changes.)
2138 TestStanzas
-> listToMaybe [v | v
<- maybeToList tests
, _
<- PD
.testSuites elabPkgDescription
]
2139 BenchStanzas
-> listToMaybe [v | v
<- maybeToList benchmarks
, _
<- PD
.benchmarks elabPkgDescription
]
2141 tests
, benchmarks
:: Maybe Bool
2142 tests
= perPkgOptionMaybe pkgid packageConfigTests
2143 benchmarks
= perPkgOptionMaybe pkgid packageConfigBenchmarks
2145 -- This is a placeholder which will get updated by 'pruneInstallPlanPass1'
2146 -- and 'pruneInstallPlanPass2'. We can't populate it here
2147 -- because whether or not tests/benchmarks should be enabled
2148 -- is heuristically calculated based on whether or not the
2149 -- dependencies of the test suite have already been installed,
2150 -- but this function doesn't know what is installed (since
2151 -- we haven't improved the plan yet), so we do it in another pass.
2152 -- Check the comments of those functions for more details.
2153 elabConfigureTargets
= []
2154 elabBuildTargets
= []
2155 elabTestTargets
= []
2156 elabBenchTargets
= []
2158 elabHaddockTargets
= []
2161 perPkgOptionFlag pkgid
False packageConfigDocumentation
2163 elabPkgSourceLocation
= srcloc
2164 elabPkgSourceHash
= Map
.lookup pkgid sourcePackageHashes
2165 elabLocalToProject
= isLocalToProject pkg
2167 if shouldBuildInplaceOnly pkg
2168 then BuildInplaceOnly OnDisk
2169 else BuildAndInstall
2170 elabPackageDbs
= projectConfigPackageDBs sharedPackageConfig
2171 elabBuildPackageDBStack
= buildAndRegisterDbs
2172 elabRegisterPackageDBStack
= buildAndRegisterDbs
2174 elabSetupScriptStyle
= packageSetupScriptStyle elabPkgDescription
2175 elabSetupScriptCliVersion
=
2176 packageSetupScriptSpecVersion
2177 elabSetupScriptStyle
2181 elabSetupPackageDBStack
= buildAndRegisterDbs
2183 elabInplaceBuildPackageDBStack
= inplacePackageDbs
2184 elabInplaceRegisterPackageDBStack
= inplacePackageDbs
2185 elabInplaceSetupPackageDBStack
= inplacePackageDbs
2188 | shouldBuildInplaceOnly pkg
= inplacePackageDbs
2189 |
otherwise = corePackageDbs
2191 elabPkgDescriptionOverride
= descOverride
2193 elabVanillaLib
= perPkgOptionFlag pkgid
True packageConfigVanillaLib
-- TODO: [required feature]: also needs to be handled recursively
2194 elabSharedLib
= pkgid `Set
.member` pkgsUseSharedLibrary
2195 elabStaticLib
= perPkgOptionFlag pkgid
False packageConfigStaticLib
2196 elabDynExe
= perPkgOptionFlag pkgid
False packageConfigDynExe
2197 elabFullyStaticExe
= perPkgOptionFlag pkgid
False packageConfigFullyStaticExe
2198 elabGHCiLib
= perPkgOptionFlag pkgid
False packageConfigGHCiLib
-- TODO: [required feature] needs to default to enabled on windows still
2199 elabProfExe
= perPkgOptionFlag pkgid
False packageConfigProf
2200 elabProfLib
= pkgid `Set
.member` pkgsUseProfilingLibrary
2205 perPkgOptionLibExeFlag
2208 packageConfigProfDetail
2209 packageConfigProfLibDetail
2210 elabCoverage
= perPkgOptionFlag pkgid
False packageConfigCoverage
2212 elabOptimization
= perPkgOptionFlag pkgid NormalOptimisation packageConfigOptimization
2213 elabSplitObjs
= perPkgOptionFlag pkgid
False packageConfigSplitObjs
2214 elabSplitSections
= perPkgOptionFlag pkgid
False packageConfigSplitSections
2215 elabStripLibs
= perPkgOptionFlag pkgid
False packageConfigStripLibs
2216 elabStripExes
= perPkgOptionFlag pkgid
False packageConfigStripExes
2217 elabDebugInfo
= perPkgOptionFlag pkgid NoDebugInfo packageConfigDebugInfo
2218 elabDumpBuildInfo
= perPkgOptionFlag pkgid NoDumpBuildInfo packageConfigDumpBuildInfo
2220 -- Combine the configured compiler prog settings with the user-supplied
2221 -- config. For the compiler progs any user-supplied config was taken
2222 -- into account earlier when configuring the compiler so its ok that
2223 -- our configured settings for the compiler override the user-supplied
2227 [ (programId prog
, programPath prog
)
2228 | prog
<- configuredPrograms compilerprogdb
2230 <> perPkgOptionMapLast pkgid packageConfigProgramPaths
2233 [ (programId prog
, args
)
2234 | prog
<- configuredPrograms compilerprogdb
2235 , let args
= programOverrideArgs prog
2238 <> perPkgOptionMapMappend pkgid packageConfigProgramArgs
2239 elabProgramPathExtra
= perPkgOptionNubList pkgid packageConfigProgramPathExtra
2240 elabConfigureScriptArgs
= perPkgOptionList pkgid packageConfigConfigureArgs
2241 elabExtraLibDirs
= perPkgOptionList pkgid packageConfigExtraLibDirs
2242 elabExtraLibDirsStatic
= perPkgOptionList pkgid packageConfigExtraLibDirsStatic
2243 elabExtraFrameworkDirs
= perPkgOptionList pkgid packageConfigExtraFrameworkDirs
2244 elabExtraIncludeDirs
= perPkgOptionList pkgid packageConfigExtraIncludeDirs
2245 elabProgPrefix
= perPkgOptionMaybe pkgid packageConfigProgPrefix
2246 elabProgSuffix
= perPkgOptionMaybe pkgid packageConfigProgSuffix
2248 elabHaddockHoogle
= perPkgOptionFlag pkgid
False packageConfigHaddockHoogle
2249 elabHaddockHtml
= perPkgOptionFlag pkgid
False packageConfigHaddockHtml
2250 elabHaddockHtmlLocation
= perPkgOptionMaybe pkgid packageConfigHaddockHtmlLocation
2251 elabHaddockForeignLibs
= perPkgOptionFlag pkgid
False packageConfigHaddockForeignLibs
2252 elabHaddockForHackage
= perPkgOptionFlag pkgid Cabal
.ForDevelopment packageConfigHaddockForHackage
2253 elabHaddockExecutables
= perPkgOptionFlag pkgid
False packageConfigHaddockExecutables
2254 elabHaddockTestSuites
= perPkgOptionFlag pkgid
False packageConfigHaddockTestSuites
2255 elabHaddockBenchmarks
= perPkgOptionFlag pkgid
False packageConfigHaddockBenchmarks
2256 elabHaddockInternal
= perPkgOptionFlag pkgid
False packageConfigHaddockInternal
2257 elabHaddockCss
= perPkgOptionMaybe pkgid packageConfigHaddockCss
2258 elabHaddockLinkedSource
= perPkgOptionFlag pkgid
False packageConfigHaddockLinkedSource
2259 elabHaddockQuickJump
= perPkgOptionFlag pkgid
False packageConfigHaddockQuickJump
2260 elabHaddockHscolourCss
= perPkgOptionMaybe pkgid packageConfigHaddockHscolourCss
2261 elabHaddockContents
= perPkgOptionMaybe pkgid packageConfigHaddockContents
2262 elabHaddockIndex
= perPkgOptionMaybe pkgid packageConfigHaddockIndex
2263 elabHaddockBaseUrl
= perPkgOptionMaybe pkgid packageConfigHaddockBaseUrl
2264 elabHaddockLib
= perPkgOptionMaybe pkgid packageConfigHaddockLib
2265 elabHaddockOutputDir
= perPkgOptionMaybe pkgid packageConfigHaddockOutputDir
2267 elabTestMachineLog
= perPkgOptionMaybe pkgid packageConfigTestMachineLog
2268 elabTestHumanLog
= perPkgOptionMaybe pkgid packageConfigTestHumanLog
2269 elabTestShowDetails
= perPkgOptionMaybe pkgid packageConfigTestShowDetails
2270 elabTestKeepTix
= perPkgOptionFlag pkgid
False packageConfigTestKeepTix
2271 elabTestWrapper
= perPkgOptionMaybe pkgid packageConfigTestWrapper
2272 elabTestFailWhenNoTestSuites
= perPkgOptionFlag pkgid
False packageConfigTestFailWhenNoTestSuites
2273 elabTestTestOptions
= perPkgOptionList pkgid packageConfigTestTestOptions
2275 elabBenchmarkOptions
= perPkgOptionList pkgid packageConfigBenchmarkOptions
2277 perPkgOptionFlag
:: PackageId
-> a
-> (PackageConfig
-> Flag a
) -> a
2278 perPkgOptionMaybe
:: PackageId
-> (PackageConfig
-> Flag a
) -> Maybe a
2279 perPkgOptionList
:: PackageId
-> (PackageConfig
-> [a
]) -> [a
]
2281 perPkgOptionFlag pkgid def f
= fromFlagOrDefault def
(lookupPerPkgOption pkgid f
)
2282 perPkgOptionMaybe pkgid f
= flagToMaybe
(lookupPerPkgOption pkgid f
)
2283 perPkgOptionList pkgid f
= lookupPerPkgOption pkgid f
2284 perPkgOptionNubList pkgid f
= fromNubList
(lookupPerPkgOption pkgid f
)
2285 perPkgOptionMapLast pkgid f
= getMapLast
(lookupPerPkgOption pkgid f
)
2286 perPkgOptionMapMappend pkgid f
= getMapMappend
(lookupPerPkgOption pkgid f
)
2288 perPkgOptionLibExeFlag pkgid def fboth flib
= (exe
, lib
)
2290 exe
= fromFlagOrDefault def bothflag
2291 lib
= fromFlagOrDefault def
(bothflag
<> libflag
)
2293 bothflag
= lookupPerPkgOption pkgid fboth
2294 libflag
= lookupPerPkgOption pkgid flib
2297 :: (Package pkg
, Monoid m
)
2299 -> (PackageConfig
-> m
)
2301 lookupPerPkgOption pkg f
=
2302 -- This is where we merge the options from the project config that
2303 -- apply to all packages, all project local packages, and to specific
2305 global `mappend` local `mappend` perpkg
2307 global
= f allPackagesConfig
2309 | isLocalToProject pkg
=
2310 f localPackagesConfig
2313 perpkg
= maybe mempty f
(Map
.lookup (packageName pkg
) perPackageConfig
)
2317 ++ [distPackageDB
(compilerId compiler
)]
2321 (storePackageDBStack
(compilerId compiler
))
2322 (projectConfigPackageDBs sharedPackageConfig
)
2324 -- For this local build policy, every package that lives in a local source
2325 -- dir (as opposed to a tarball), or depends on such a package, will be
2326 -- built inplace into a shared dist dir. Tarball packages that depend on
2327 -- source dir packages will also get unpacked locally.
2328 shouldBuildInplaceOnly
:: SolverPackage loc
-> Bool
2329 shouldBuildInplaceOnly pkg
=
2332 pkgsToBuildInplaceOnly
2334 pkgsToBuildInplaceOnly
:: Set PackageId
2335 pkgsToBuildInplaceOnly
=
2338 SolverInstallPlan
.reverseDependencyClosure
2340 (map PlannedId
(Set
.toList pkgsLocalToProject
))
2342 isLocalToProject
:: Package pkg
=> pkg
-> Bool
2343 isLocalToProject pkg
=
2348 pkgsLocalToProject
:: Set PackageId
2349 pkgsLocalToProject
=
2350 Set
.fromList
(catMaybes (map shouldBeLocal localPackages
))
2351 -- TODO: localPackages is a misnomer, it's all project packages
2352 -- here is where we decide which ones will be local!
2354 pkgsUseSharedLibrary
:: Set PackageId
2355 pkgsUseSharedLibrary
=
2356 packagesWithLibDepsDownwardClosedProperty needsSharedLib
2358 needsSharedLib pkg
=
2360 compilerShouldUseSharedLibByDefault
2361 (liftM2 (||
) pkgSharedLib pkgDynExe
)
2363 pkgid
= packageId pkg
2364 pkgSharedLib
= perPkgOptionMaybe pkgid packageConfigSharedLib
2365 pkgDynExe
= perPkgOptionMaybe pkgid packageConfigDynExe
2367 -- TODO: [code cleanup] move this into the Cabal lib. It's currently open
2368 -- coded in Distribution.Simple.Configure, but should be made a proper
2369 -- function of the Compiler or CompilerInfo.
2370 compilerShouldUseSharedLibByDefault
=
2371 case compilerFlavor compiler
of
2372 GHC
-> GHC
.isDynamic compiler
2373 GHCJS
-> GHCJS
.isDynamic compiler
2376 pkgsUseProfilingLibrary
:: Set PackageId
2377 pkgsUseProfilingLibrary
=
2378 packagesWithLibDepsDownwardClosedProperty needsProfilingLib
2380 needsProfilingLib pkg
=
2381 fromFlagOrDefault
False (profBothFlag
<> profLibFlag
)
2383 pkgid
= packageId pkg
2384 profBothFlag
= lookupPerPkgOption pkgid packageConfigProf
2385 profLibFlag
= lookupPerPkgOption pkgid packageConfigProfLib
2386 -- TODO: [code cleanup] unused: the old deprecated packageConfigProfExe
2389 Graph
.fromDistinctList
$
2391 NonSetupLibDepSolverPlanPackage
2392 (SolverInstallPlan
.toList solverPlan
)
2394 packagesWithLibDepsDownwardClosedProperty property
=
2401 | pkg
<- SolverInstallPlan
.toList solverPlan
2402 , property pkg
-- just the packages that satisfy the property
2403 -- TODO: [nice to have] this does not check the config consistency,
2404 -- e.g. a package explicitly turning off profiling, but something
2405 -- depending on it that needs profiling. This really needs a separate
2406 -- package config validation/resolution pass.
2409 -- TODO: [nice to have] config consistency checking:
2410 -- + profiling libs & exes, exe needs lib, recursive
2411 -- + shared libs & exes, exe needs lib, recursive
2412 -- + vanilla libs & exes, exe needs lib, recursive
2413 -- + ghci or shared lib needed by TH, recursive, ghc version dependent
2415 -- TODO: Drop matchPlanPkg/matchElabPkg in favor of mkCCMapping
2417 shouldBeLocal
:: PackageSpecifier
(SourcePackage
(PackageLocation loc
)) -> Maybe PackageId
2418 shouldBeLocal NamedPackage
{} = Nothing
2419 shouldBeLocal
(SpecificSourcePackage pkg
) = case srcpkgSource pkg
of
2420 LocalUnpackedPackage _
-> Just
(packageId pkg
)
2423 -- | Given a 'ElaboratedPlanPackage', report if it matches a 'ComponentName'.
2424 matchPlanPkg
:: (ComponentName
-> Bool) -> ElaboratedPlanPackage
-> Bool
2425 matchPlanPkg p
= InstallPlan
.foldPlanPackage
(p
. ipiComponentName
) (matchElabPkg p
)
2427 -- | Get the appropriate 'ComponentName' which identifies an installed
2429 ipiComponentName
:: IPI
.InstalledPackageInfo
-> ComponentName
2430 ipiComponentName
= CLibName
. IPI
.sourceLibName
2432 -- | Given a 'ElaboratedConfiguredPackage', report if it matches a
2434 matchElabPkg
:: (ComponentName
-> Bool) -> ElaboratedConfiguredPackage
-> Bool
2435 matchElabPkg p elab
=
2436 case elabPkgOrComp elab
of
2437 ElabComponent comp
-> maybe False p
(compComponentName comp
)
2439 -- So, what should we do here? One possibility is to
2440 -- unconditionally return 'True', because whatever it is
2441 -- that we're looking for, it better be in this package.
2442 -- But this is a bit dodgy if the package doesn't actually
2443 -- have, e.g., a library. Fortunately, it's not possible
2444 -- for the build of the library/executables to be toggled
2445 -- by 'pkgStanzasEnabled', so the only thing we have to
2446 -- test is if the component in question is *buildable.*
2449 (Cabal
.pkgBuildableComponents
(elabPkgDescription elab
))
2451 -- | Given an 'ElaboratedPlanPackage', generate the mapping from 'PackageName'
2452 -- and 'ComponentName' to the 'ComponentId' that should be used
2455 :: ElaboratedPlanPackage
2456 -> (PackageName
, Map ComponentName
(AnnotatedId ComponentId
))
2458 InstallPlan
.foldPlanPackage
2462 (ipiComponentName ipkg
)
2465 { ann_id
= IPI
.installedComponentId ipkg
2466 , ann_pid
= packageId ipkg
2467 , ann_cname
= IPI
.sourceComponentName ipkg
2475 { ann_id
= elabComponentId elab
2476 , ann_pid
= packageId elab
2479 in ( packageName elab
2480 , case elabPkgOrComp elab
of
2481 ElabComponent comp
->
2482 case compComponentName comp
of
2483 Nothing
-> Map
.empty
2484 Just n
-> Map
.singleton n
(mk_aid n
)
2488 (\comp
-> let cn
= Cabal
.componentName comp
in (cn
, mk_aid cn
))
2489 (Cabal
.pkgBuildableComponents
(elabPkgDescription elab
))
2492 -- | Given an 'ElaboratedPlanPackage', generate the mapping from 'ComponentId'
2493 -- to the shape of this package, as per mix-in linking.
2495 :: ElaboratedPlanPackage
2496 -> (ComponentId
, (OpenUnitId
, ModuleShape
))
2497 mkShapeMapping dpkg
=
2498 (getComponentId dpkg
, (indef_uid
, shape
))
2501 InstallPlan
.foldPlanPackage
2503 (liftM2 (,) IPI
.installedComponentId shapeInstalledPackage
)
2504 (liftM2 (,) elabComponentId elabModuleShape
)
2510 [ (req
, OpenModuleVar req
)
2511 | req
<- Set
.toList
(modShapeRequires shape
)
2515 -- | Get the bin\/ directories that a package's executables should reside in.
2517 -- The result may be empty if the package does not build any executables.
2519 -- The result may have several entries if this is an inplace build of a package
2520 -- with multiple executables.
2523 -> ElaboratedSharedConfig
2524 -> ElaboratedConfiguredPackage
2526 binDirectories layout config package
= case elabBuildStyle package
of
2527 -- quick sanity check: no sense returning a bin directory if we're not going
2528 -- to put any executables in it, that will just clog up the PATH
2529 _ | noExecutables
-> []
2530 BuildAndInstall
-> [installedBinDirectory package
]
2531 BuildInplaceOnly
{} -> map (root
</>) $ case elabPkgOrComp package
of
2532 ElabComponent comp
-> case compSolverName comp
of
2533 CD
.ComponentExe n
-> [prettyShow n
]
2536 map (prettyShow
. PD
.exeName
)
2538 . elabPkgDescription
2541 noExecutables
= null . PD
.executables
. elabPkgDescription
$ package
2543 distBuildDirectory layout
(elabDistDirParams config package
)
2546 type InstS
= Map UnitId ElaboratedPlanPackage
2547 type InstM a
= State InstS a
2550 :: ElaboratedPlanPackage
2552 getComponentId
(InstallPlan
.PreExisting dipkg
) = IPI
.installedComponentId dipkg
2553 getComponentId
(InstallPlan
.Configured elab
) = elabComponentId elab
2554 getComponentId
(InstallPlan
.Installed elab
) = elabComponentId elab
2556 extractElabBuildStyle
2557 :: InstallPlan
.GenericPlanPackage ipkg ElaboratedConfiguredPackage
2559 extractElabBuildStyle
(InstallPlan
.Configured elab
) = elabBuildStyle elab
2560 extractElabBuildStyle _
= BuildAndInstall
2562 -- instantiateInstallPlan is responsible for filling out an InstallPlan
2563 -- with all of the extra Configured packages that would be generated by
2564 -- recursively instantiating the dependencies of packages.
2566 -- Suppose we are compiling the following packages:
2572 -- dependency f[H=containers:Data.Map]
2574 -- At entry, we have an InstallPlan with a single plan package per
2575 -- actual source package, e.g., only (indefinite!) f and g. The job of
2576 -- instantiation is to turn this into three plan packages: each of the
2577 -- packages as before, but also a new, definite package f[H=containers:Data.Map]
2579 -- How do we do this? The general strategy is to iterate over every
2580 -- package in the existing plan and recursively create new entries for
2581 -- each of its dependencies which is an instantiated package (e.g.,
2582 -- f[H=p:G]). This process must be recursive, as f itself may depend on
2583 -- OTHER packages which it instantiated using its hole H.
2587 -- * We have to keep track of whether or not we are instantiating with
2588 -- inplace packages, because instantiating a non-inplace package with
2589 -- an inplace packages makes it inplace (since it depends on
2590 -- something in the inplace store)! The rule is that if any of the
2591 -- modules in an instantiation are inplace, then the instantiated
2592 -- unit itself must be inplace. There is then a bunch of faffing
2593 -- about to keep track of BuildStyle.
2595 -- * ElaboratedConfiguredPackage was never really designed for post
2596 -- facto instantiation, so some of the steps for generating new
2597 -- instantiations are a little fraught. For example, the act of
2598 -- flipping a package to be inplace involves faffing about with four
2599 -- fields, because these fields are precomputed. A good refactor
2600 -- would be to reduce the amount of precomputation to simplify the
2603 -- * We use the state monad to cache already instantiated modules, so
2604 -- we don't instantiate the same thing multiple times.
2606 instantiateInstallPlan
:: StoreDirLayout
-> InstallDirs
.InstallDirTemplates
-> ElaboratedSharedConfig
-> ElaboratedInstallPlan
-> ElaboratedInstallPlan
2607 instantiateInstallPlan storeDirLayout defaultInstallDirs elaboratedShared plan
=
2609 (IndependentGoals
False)
2610 (Graph
.fromDistinctList
(Map
.elems ready_map
))
2612 pkgs
= InstallPlan
.toList plan
2614 cmap
= Map
.fromList
[(getComponentId pkg
, pkg
) | pkg
<- pkgs
]
2618 -> Map ModuleName
(Module
, BuildStyle
)
2619 -> InstM
(DefUnitId
, BuildStyle
)
2620 instantiateUnitId cid insts
= state
$ \s
->
2621 case Map
.lookup uid s
of
2624 -- TODO: I don't think the knot tying actually does
2628 (instantiateComponent uid cid insts
)
2629 (Map
.insert uid r s
)
2630 in ((def_uid
, extractElabBuildStyle r
), Map
.insert uid r s
')
2631 Just r
-> ((def_uid
, extractElabBuildStyle r
), s
)
2633 def_uid
= mkDefUnitId cid
(fmap fst insts
)
2634 uid
= unDefUnitId def_uid
2636 -- No need to InplaceT; the inplace-ness is properly computed for
2637 -- the ElaboratedPlanPackage, so that will implicitly pass it on
2638 instantiateComponent
2641 -> Map ModuleName
(Module
, BuildStyle
)
2642 -> InstM ElaboratedPlanPackage
2643 instantiateComponent uid cid insts
2644 | Just planpkg
<- Map
.lookup cid cmap
=
2646 InstallPlan
.Configured
2647 ( elab0
@ElaboratedConfiguredPackage
2648 { elabPkgOrComp
= ElabComponent comp
2652 traverse
(fmap fst . substUnitId insts
) (compLinkedLibDependencies comp
)
2653 let build_style
= fold
(fmap snd insts
)
2654 let getDep
(Module dep_uid _
) = [dep_uid
]
2656 fixupBuildStyle build_style
$
2659 , elabComponentId
= cid
2660 , elabInstantiatedWith
= fmap fst insts
2661 , elabIsCanonical
= Map
.null (fmap fst insts
)
2665 { compOrderLibDependencies
=
2666 (if Map
.null insts
then [] else [newSimpleUnitId cid
])
2670 (deps
++ concatMap (getDep
. fst) (Map
.elems insts
))
2683 return $ InstallPlan
.Configured elab
2685 |
otherwise = error ("instantiateComponent: " ++ prettyShow cid
)
2687 substUnitId
:: Map ModuleName
(Module
, BuildStyle
) -> OpenUnitId
-> InstM
(DefUnitId
, BuildStyle
)
2688 substUnitId _
(DefiniteUnitId uid
) =
2689 -- This COULD actually, secretly, be an inplace package, but in
2690 -- that case it doesn't matter as it's already been recorded
2691 -- in the package that depends on this
2692 return (uid
, BuildAndInstall
)
2693 substUnitId subst
(IndefFullUnitId cid insts
) = do
2694 insts
' <- substSubst subst insts
2695 instantiateUnitId cid insts
'
2697 -- NB: NOT composition
2699 :: Map ModuleName
(Module
, BuildStyle
)
2700 -> Map ModuleName OpenModule
2701 -> InstM
(Map ModuleName
(Module
, BuildStyle
))
2702 substSubst subst insts
= traverse
(substModule subst
) insts
2704 substModule
:: Map ModuleName
(Module
, BuildStyle
) -> OpenModule
-> InstM
(Module
, BuildStyle
)
2705 substModule subst
(OpenModuleVar mod_name
)
2706 | Just m
<- Map
.lookup mod_name subst
= return m
2707 |
otherwise = error "substModule: non-closing substitution"
2708 substModule subst
(OpenModule uid mod_name
) = do
2709 (uid
', build_style
) <- substUnitId subst uid
2710 return (Module uid
' mod_name
, build_style
)
2712 indefiniteUnitId
:: ComponentId
-> InstM UnitId
2713 indefiniteUnitId cid
= do
2714 let uid
= newSimpleUnitId cid
2715 r
<- indefiniteComponent uid cid
2716 state
$ \s
-> (uid
, Map
.insert uid r s
)
2718 indefiniteComponent
:: UnitId
-> ComponentId
-> InstM ElaboratedPlanPackage
2719 indefiniteComponent _uid cid
2720 -- Only need Configured; this phase happens before improvement, so
2721 -- there shouldn't be any Installed packages here.
2722 | Just
(InstallPlan
.Configured epkg
) <- Map
.lookup cid cmap
2723 , ElabComponent elab_comp
<- elabPkgOrComp epkg
=
2725 -- We need to do a little more processing of the includes: some
2726 -- of them are fully definite even without substitution. We
2727 -- want to build those too; see #5634.
2729 -- This code mimics similar code in Distribution.Backpack.ReadyComponent;
2730 -- however, unlike the conversion from LinkedComponent to
2731 -- ReadyComponent, this transformation is done *without*
2732 -- changing the type in question; and what we are simply
2733 -- doing is enforcing tighter invariants on the data
2734 -- structure in question. The new invariant is that there
2735 -- is no IndefFullUnitId in compLinkedLibDependencies that actually
2736 -- has no holes. We couldn't specify this invariant when
2737 -- we initially created the ElaboratedPlanPackage because
2738 -- we have no way of actually reifying the UnitId into a
2739 -- DefiniteUnitId (that's what substUnitId does!)
2740 new_deps
<- for
(compLinkedLibDependencies elab_comp
) $ \uid
->
2741 if Set
.null (openUnitIdFreeHoles uid
)
2742 then fmap (DefiniteUnitId
. fst) (substUnitId Map
.empty uid
)
2744 -- NB: no fixupBuildStyle needed here, as if the indefinite
2745 -- component depends on any inplace packages, it itself must
2746 -- be indefinite! There is no substitution here, we can't
2747 -- post facto add inplace deps
2748 return . InstallPlan
.Configured
$
2753 { compLinkedLibDependencies
= new_deps
2754 , -- I think this is right: any new definite unit ids we
2755 -- minted in the phase above need to be built before us.
2756 -- Add 'em in. This doesn't remove any old dependencies
2757 -- on the indefinite package; they're harmless.
2758 compOrderLibDependencies
=
2760 compOrderLibDependencies elab_comp
2761 ++ [unDefUnitId d | DefiniteUnitId d
<- new_deps
]
2764 | Just planpkg
<- Map
.lookup cid cmap
=
2766 |
otherwise = error ("indefiniteComponent: " ++ prettyShow cid
)
2768 fixupBuildStyle BuildAndInstall elab
= elab
2769 fixupBuildStyle _
(elab
@ElaboratedConfiguredPackage
{elabBuildStyle
= BuildInplaceOnly
{}}) = elab
2770 fixupBuildStyle t
@(BuildInplaceOnly
{}) elab
=
2772 { elabBuildStyle
= t
2773 , elabBuildPackageDBStack
= elabInplaceBuildPackageDBStack elab
2774 , elabRegisterPackageDBStack
= elabInplaceRegisterPackageDBStack elab
2775 , elabSetupPackageDBStack
= elabInplaceSetupPackageDBStack elab
2778 ready_map
= execState work Map
.empty
2780 work
= for_ pkgs
$ \pkg
->
2782 InstallPlan
.Configured elab
2783 |
not (Map
.null (elabLinkedInstantiatedWith elab
)) ->
2784 indefiniteUnitId
(elabComponentId elab
)
2787 instantiateUnitId
(getComponentId pkg
) Map
.empty
2790 ---------------------------
2794 -- Refer to ProjectPlanning.Types for details of these important types:
2796 -- data ComponentTarget = ...
2797 -- data SubComponentTarget = ...
2799 -- One step in the build system is to translate higher level intentions like
2800 -- "build this package", "test that package", or "repl that component" into
2801 -- a more detailed specification of exactly which components to build (or other
2802 -- actions like repl or build docs). This translation is somewhat different for
2803 -- different commands. For example "test" for a package will build a different
2804 -- set of components than "build". In addition, the translation of these
2805 -- intentions can fail. For example "run" for a package is only unambiguous
2806 -- when the package has a single executable.
2808 -- So we need a little bit of infrastructure to make it easy for the command
2809 -- implementations to select what component targets are meant when a user asks
2810 -- to do something with a package or component. To do this (and to be able to
2811 -- produce good error messages for mistakes and when targets are not available)
2812 -- we need to gather and summarise accurate information about all the possible
2813 -- targets, both available and unavailable. Then a command implementation can
2814 -- decide which of the available component targets should be selected.
2816 -- | An available target represents a component within a package that a user
2817 -- command could plausibly refer to. In this sense, all the components defined
2818 -- within the package are things the user could refer to, whether or not it
2819 -- would actually be possible to build that component.
2821 -- In particular the available target contains an 'AvailableTargetStatus' which
2822 -- informs us about whether it's actually possible to select this component to
2823 -- be built, and if not why not. This detail makes it possible for command
2824 -- implementations (like @build@, @test@ etc) to accurately report why a target
2827 -- Note that the type parameter is used to help enforce that command
2828 -- implementations can only select targets that can actually be built (by
2829 -- forcing them to return the @k@ value for the selected targets).
2830 -- In particular 'resolveTargets' makes use of this (with @k@ as
2831 -- @('UnitId', ComponentName')@) to identify the targets thus selected.
2832 data AvailableTarget k
= AvailableTarget
2833 { availableTargetPackageId
:: PackageId
2834 , availableTargetComponentName
:: ComponentName
2835 , availableTargetStatus
:: AvailableTargetStatus k
2836 , availableTargetLocalToProject
:: Bool
2838 deriving (Eq
, Show, Functor
)
2840 -- | The status of a an 'AvailableTarget' component. This tells us whether
2841 -- it's actually possible to select this component to be built, and if not
2843 data AvailableTargetStatus k
2844 = -- | When the user does @tests: False@
2845 TargetDisabledByUser
2846 |
-- | When the solver could not enable tests
2847 TargetDisabledBySolver
2848 |
-- | When the component has @buildable: False@
2850 |
-- | When the component is non-core in a non-local package
2852 |
-- | The target can or should be built
2853 TargetBuildable k TargetRequested
2854 deriving (Eq
, Ord
, Show, Functor
)
2856 -- | This tells us whether a target ought to be built by default, or only if
2857 -- specifically requested. The policy is that components like libraries and
2858 -- executables are built by default by @build@, but test suites and benchmarks
2859 -- are not, unless this is overridden in the project configuration.
2860 data TargetRequested
2861 = -- | To be built by default
2862 TargetRequestedByDefault
2863 |
-- | Not to be built by default
2864 TargetNotRequestedByDefault
2865 deriving (Eq
, Ord
, Show)
2867 -- | Given the install plan, produce the set of 'AvailableTarget's for each
2868 -- package-component pair.
2870 -- Typically there will only be one such target for each component, but for
2871 -- example if we have a plan with both normal and profiling variants of a
2872 -- component then we would get both as available targets, or similarly if we
2873 -- had a plan that contained two instances of the same version of a package.
2874 -- This approach makes it relatively easy to select all instances\/variants
2877 :: ElaboratedInstallPlan
2879 (PackageId
, ComponentName
)
2880 [AvailableTarget
(UnitId
, ComponentName
)]
2881 availableTargets installPlan
=
2883 [ (pkgid
, cname
, fake
, target
)
2884 | pkg
<- InstallPlan
.toList installPlan
2885 , (pkgid
, cname
, fake
, target
) <- case pkg
of
2886 InstallPlan
.PreExisting ipkg
-> availableInstalledTargets ipkg
2887 InstallPlan
.Installed elab
-> availableSourceTargets elab
2888 InstallPlan
.Configured elab
-> availableSourceTargets elab
2893 [ ((pkgid
, cname
), [target
])
2894 |
(pkgid
, cname
, fake
, target
) <- rs
2899 [ ((pkgid
, cname
), [target
])
2900 |
(pkgid
, cname
, fake
, target
) <- rs
2905 -- The normal targets mask the fake ones. We get all instances of the
2906 -- normal ones and only one copy of the fake ones (as there are many
2907 -- duplicates of the fake ones). See 'availableSourceTargets' below for
2908 -- more details on this fake stuff is about.
2910 availableInstalledTargets
2911 :: IPI
.InstalledPackageInfo
2915 , AvailableTarget
(UnitId
, ComponentName
)
2918 availableInstalledTargets ipkg
=
2919 let unitid
= installedUnitId ipkg
2920 cname
= CLibName LMainLibName
2921 status
= TargetBuildable
(unitid
, cname
) TargetRequestedByDefault
2922 target
= AvailableTarget
(packageId ipkg
) cname status
False
2924 in [(packageId ipkg
, cname
, fake
, target
)]
2926 availableSourceTargets
2927 :: ElaboratedConfiguredPackage
2931 , AvailableTarget
(UnitId
, ComponentName
)
2934 availableSourceTargets elab
=
2935 -- We have a somewhat awkward problem here. We need to know /all/ the
2936 -- components from /all/ the packages because these are the things that
2937 -- users could refer to. Unfortunately, at this stage the elaborated install
2938 -- plan does /not/ contain all components: some components have already
2939 -- been deleted because they cannot possibly be built. This is the case
2940 -- for components that are marked @buildable: False@ in their .cabal files.
2941 -- (It's not unreasonable that the unbuildable components have been pruned
2942 -- as the plan invariant is considerably simpler if all nodes can be built)
2944 -- We can recover the missing components but it's not exactly elegant. For
2945 -- a graph node corresponding to a component we still have the information
2946 -- about the package that it came from, and this includes the names of
2947 -- /all/ the other components in the package. So in principle this lets us
2948 -- find the names of all components, plus full details of the buildable
2951 -- Consider for example a package with 3 exe components: foo, bar and baz
2952 -- where foo and bar are buildable, but baz is not. So the plan contains
2953 -- nodes for the components foo and bar. Now we look at each of these two
2954 -- nodes and look at the package they come from and the names of the
2955 -- components in this package. This will give us the names foo, bar and
2956 -- baz, twice (once for each of the two buildable components foo and bar).
2958 -- We refer to these reconstructed missing components as fake targets.
2959 -- It is an invariant that they are not available to be built.
2961 -- To produce the final set of targets we put the fake targets in a finite
2962 -- map (thus eliminating the duplicates) and then we overlay that map with
2963 -- the normal buildable targets. (This is done above in 'availableTargets'.)
2965 [ (packageId elab
, cname
, fake
, target
)
2966 | component
<- pkgComponents
(elabPkgDescription elab
)
2967 , let cname
= componentName component
2968 status
= componentAvailableTargetStatus component
2971 { availableTargetPackageId
= packageId elab
2972 , availableTargetComponentName
= cname
2973 , availableTargetStatus
= status
2974 , availableTargetLocalToProject
= elabLocalToProject elab
2976 fake
= isFakeTarget cname
2977 , -- TODO: The goal of this test is to exclude "instantiated"
2978 -- packages as available targets. This means that you can't
2979 -- ask for a particular instantiated component to be built;
2980 -- it will only get built by a dependency. Perhaps the
2981 -- correct way to implement this is to run selection
2982 -- prior to instantiating packages. If you refactor
2983 -- this, then you can delete this test.
2984 elabIsCanonical elab
2985 , -- Filter out some bogus parts of the cross product that are never needed
2987 TargetBuildable
{} | fake
-> False
2991 isFakeTarget cname
=
2992 case elabPkgOrComp elab
of
2993 ElabPackage _
-> False
2994 ElabComponent elabComponent
->
2995 compComponentName elabComponent
2998 componentAvailableTargetStatus
2999 :: Component
-> AvailableTargetStatus
(UnitId
, ComponentName
)
3000 componentAvailableTargetStatus component
=
3001 case componentOptionalStanza
$ CD
.componentNameToComponent cname
of
3002 -- it is not an optional stanza, so a library, exe or foreign lib
3004 |
not buildable
-> TargetNotBuildable
3007 (elabUnitId elab
, cname
)
3008 TargetRequestedByDefault
3009 -- it is not an optional stanza, so a testsuite or benchmark
3011 case ( optStanzaLookup stanza
(elabStanzasRequested elab
) -- TODO
3012 , optStanzaSetMember stanza
(elabStanzasAvailable elab
)
3014 _ |
not withinPlan
-> TargetNotLocal
3015 (Just
False, _
) -> TargetDisabledByUser
3016 (Nothing
, False) -> TargetDisabledBySolver
3017 _ |
not buildable
-> TargetNotBuildable
3018 (Just
True, True) ->
3020 (elabUnitId elab
, cname
)
3021 TargetRequestedByDefault
3024 (elabUnitId elab
, cname
)
3025 TargetNotRequestedByDefault
3026 (Just
True, False) ->
3027 error $ "componentAvailableTargetStatus: impossible; cname=" ++ prettyShow cname
3029 cname
= componentName component
3030 buildable
= PD
.buildable
(componentBuildInfo component
)
3032 elabLocalToProject elab
3033 ||
case elabPkgOrComp elab
of
3034 ElabComponent elabComponent
->
3035 compComponentName elabComponent
== Just cname
3037 case componentName component
of
3038 CLibName
(LMainLibName
) -> True
3040 -- TODO: what about sub-libs and foreign libs?
3043 -- | Merge component targets that overlap each other. Specially when we have
3044 -- multiple targets for the same component and one of them refers to the whole
3045 -- component (rather than a module or file within) then all the other targets
3046 -- for that component are subsumed.
3048 -- We also allow for information associated with each component target, and
3049 -- whenever we targets subsume each other we aggregate their associated info.
3050 nubComponentTargets
:: [(ComponentTarget
, a
)] -> [(ComponentTarget
, NonEmpty a
)]
3051 nubComponentTargets
=
3052 concatMap (wholeComponentOverrides
. map snd)
3053 . groupBy ((==) `on`
fst)
3054 . sortBy (compare `on`
fst)
3055 . map (\t@((ComponentTarget cname _
, _
)) -> (cname
, t
))
3056 . map compatSubComponentTargets
3058 -- If we're building the whole component then that the only target all we
3059 -- need, otherwise we can have several targets within the component.
3060 wholeComponentOverrides
3061 :: [(ComponentTarget
, a
)]
3062 -> [(ComponentTarget
, NonEmpty a
)]
3063 wholeComponentOverrides ts
=
3064 case [ta | ta
@(ComponentTarget _ WholeComponent
, _
) <- ts
] of
3067 -- Delete tuple (t, x) from original list to avoid duplicates.
3068 -- Use 'deleteBy', to avoid additional Class constraint on 'nubComponentTargets'.
3069 ts
' = deleteBy (\(t1
, _
) (t2
, _
) -> t1
== t2
) (t
, x
) ts
3071 [(t
, x
:|
map snd ts
')]
3072 [] -> [(t
, x
:|
[]) |
(t
, x
) <- ts
]
3074 -- Not all Cabal Setup.hs versions support sub-component targets, so switch
3075 -- them over to the whole component
3076 compatSubComponentTargets
:: (ComponentTarget
, a
) -> (ComponentTarget
, a
)
3077 compatSubComponentTargets target
@(ComponentTarget cname _subtarget
, x
)
3078 |
not setupHsSupportsSubComponentTargets
=
3079 (ComponentTarget cname WholeComponent
, x
)
3080 |
otherwise = target
3082 -- Actually the reality is that no current version of Cabal's Setup.hs
3083 -- build command actually support building specific files or modules.
3084 setupHsSupportsSubComponentTargets
= False
3086 -- TODO: when that changes, adjust this test, e.g.
3087 -- \| pkgSetupScriptCliVersion >= Version [x,y] []
3089 pkgHasEphemeralBuildTargets
:: ElaboratedConfiguredPackage
-> Bool
3090 pkgHasEphemeralBuildTargets elab
=
3091 (not . null) (elabReplTarget elab
)
3092 ||
(not . null) (elabTestTargets elab
)
3093 ||
(not . null) (elabBenchTargets elab
)
3094 ||
(not . null) (elabHaddockTargets elab
)
3096 [ () | ComponentTarget _ subtarget
<- elabBuildTargets elab
, subtarget
/= WholeComponent
3099 -- | The components that we'll build all of, meaning that after they're built
3100 -- we can skip building them again (unlike with building just some modules or
3101 -- other files within a component).
3102 elabBuildTargetWholeComponents
3103 :: ElaboratedConfiguredPackage
3104 -> Set ComponentName
3105 elabBuildTargetWholeComponents elab
=
3107 [cname | ComponentTarget cname WholeComponent
<- elabBuildTargets elab
]
3109 ------------------------------------------------------------------------------
3111 -- * Install plan pruning
3113 ------------------------------------------------------------------------------
3115 -- | How 'pruneInstallPlanToTargets' should interpret the per-package
3116 -- 'ComponentTarget's: as build, repl or haddock targets.
3118 = TargetActionConfigure
3123 | TargetActionHaddock
3125 -- | Given a set of per-package\/per-component targets, take the subset of the
3126 -- install plan needed to build those targets. Also, update the package config
3127 -- to specify which optional stanzas to enable, and which targets within each
3128 -- package to build.
3130 -- NB: Pruning happens after improvement, which is important because we
3131 -- will prune differently depending on what is already installed (to
3132 -- implement "sticky" test suite enabling behavior).
3133 pruneInstallPlanToTargets
3135 -> Map UnitId
[ComponentTarget
]
3136 -> ElaboratedInstallPlan
3137 -> ElaboratedInstallPlan
3138 pruneInstallPlanToTargets targetActionType perPkgTargetsMap elaboratedPlan
=
3139 InstallPlan
.new
(InstallPlan
.planIndepGoals elaboratedPlan
)
3140 . Graph
.fromDistinctList
3141 -- We have to do the pruning in two passes
3142 . pruneInstallPlanPass2
3143 . pruneInstallPlanPass1
3144 -- Set the targets that will be the roots for pruning
3145 . setRootTargets targetActionType perPkgTargetsMap
3146 . InstallPlan
.toList
3149 -- | This is a temporary data type, where we temporarily
3150 -- override the graph dependencies of an 'ElaboratedPackage',
3151 -- so we can take a closure over them. We'll throw out the
3152 -- overridden dependencies when we're done so it's strictly temporary.
3154 -- For 'ElaboratedComponent', this the cached unit IDs always
3155 -- coincide with the real thing.
3156 data PrunedPackage
= PrunedPackage ElaboratedConfiguredPackage
[UnitId
]
3158 instance Package PrunedPackage
where
3159 packageId
(PrunedPackage elab _
) = packageId elab
3161 instance HasUnitId PrunedPackage
where
3162 installedUnitId
= Graph
.nodeKey
3164 instance Graph
.IsNode PrunedPackage
where
3165 type Key PrunedPackage
= UnitId
3166 nodeKey
(PrunedPackage elab _
) = Graph
.nodeKey elab
3167 nodeNeighbors
(PrunedPackage _ deps
) = deps
3169 fromPrunedPackage
:: PrunedPackage
-> ElaboratedConfiguredPackage
3170 fromPrunedPackage
(PrunedPackage elab _
) = elab
3172 -- | Set the build targets based on the user targets (but not rev deps yet).
3173 -- This is required before we can prune anything.
3176 -> Map UnitId
[ComponentTarget
]
3177 -> [ElaboratedPlanPackage
]
3178 -> [ElaboratedPlanPackage
]
3179 setRootTargets targetAction perPkgTargetsMap
=
3180 assert
(not (Map
.null perPkgTargetsMap
)) $
3181 assert
(all (not . null) (Map
.elems perPkgTargetsMap
)) $
3182 map (mapConfiguredPackage setElabBuildTargets
)
3184 -- Set the targets we'll build for this package/component. This is just
3185 -- based on the root targets from the user, not targets implied by reverse
3186 -- dependencies. Those comes in the second pass once we know the rev deps.
3188 setElabBuildTargets elab
=
3189 case ( Map
.lookup (installedUnitId elab
) perPkgTargetsMap
3192 (Nothing
, _
) -> elab
3193 (Just tgts
, TargetActionConfigure
) -> elab
{elabConfigureTargets
= tgts
}
3194 (Just tgts
, TargetActionBuild
) -> elab
{elabBuildTargets
= tgts
}
3195 (Just tgts
, TargetActionTest
) -> elab
{elabTestTargets
= tgts
}
3196 (Just tgts
, TargetActionBench
) -> elab
{elabBenchTargets
= tgts
}
3197 (Just tgts
, TargetActionRepl
) ->
3199 { elabReplTarget
= tgts
3200 , elabBuildHaddocks
= False
3201 , elabBuildStyle
= BuildInplaceOnly InMemory
3203 (Just tgts
, TargetActionHaddock
) ->
3205 setElabHaddockTargets
3207 { elabHaddockTargets
= tgts
3208 , elabBuildHaddocks
= True
3213 setElabHaddockTargets tgt elab
3214 | isTestComponentTarget tgt
= elab
{elabHaddockTestSuites
= True}
3215 | isBenchComponentTarget tgt
= elab
{elabHaddockBenchmarks
= True}
3216 | isForeignLibComponentTarget tgt
= elab
{elabHaddockForeignLibs
= True}
3217 | isExeComponentTarget tgt
= elab
{elabHaddockExecutables
= True}
3218 | isSubLibComponentTarget tgt
= elab
{elabHaddockInternal
= True}
3221 minVersionReplFlagFile
:: Version
3222 minVersionReplFlagFile
= mkVersion
[3, 9]
3224 -- | Assuming we have previously set the root build targets (i.e. the user
3225 -- targets but not rev deps yet), the first pruning pass does two things:
3227 -- * A first go at determining which optional stanzas (testsuites, benchmarks)
3228 -- are needed. We have a second go in the next pass.
3229 -- * Take the dependency closure using pruned dependencies. We prune deps that
3230 -- are used only by unneeded optional stanzas. These pruned deps are only
3231 -- used for the dependency closure and are not persisted in this pass.
3232 pruneInstallPlanPass1
3233 :: [ElaboratedPlanPackage
]
3234 -> [ElaboratedPlanPackage
]
3235 pruneInstallPlanPass1 pkgs
3236 -- if there are repl targets, we need to do a bit more work
3237 -- See Note [Pruning for Multi Repl]
3238 | anyReplTarget
= final_final_graph
3239 -- otherwise we'll do less
3240 |
otherwise = pruned_packages
3242 pkgs
' :: [InstallPlan
.GenericPlanPackage IPI
.InstalledPackageInfo PrunedPackage
]
3243 pkgs
' = map (mapConfiguredPackage prune
) pkgs
3245 prune
:: ElaboratedConfiguredPackage
-> PrunedPackage
3246 prune elab
= PrunedPackage elab
' (pruneOptionalDependencies elab
')
3248 elab
' = addOptionalStanzas elab
3250 graph
= Graph
.fromDistinctList pkgs
'
3253 roots
= mapMaybe find_root pkgs
'
3255 -- Make a closed graph by calculating the closure from the roots
3256 pruned_packages
:: [ElaboratedPlanPackage
]
3257 pruned_packages
= map (mapConfiguredPackage fromPrunedPackage
) (fromMaybe [] $ Graph
.closure graph roots
)
3259 closed_graph
:: Graph
.Graph ElaboratedPlanPackage
3260 closed_graph
= Graph
.fromDistinctList pruned_packages
3262 -- whether any package has repl targets enabled.
3263 anyReplTarget
:: Bool
3264 anyReplTarget
= any is_repl_gpp pkgs
'
3266 is_repl_gpp
(InstallPlan
.Configured pkg
) = is_repl_pp pkg
3267 is_repl_gpp _
= False
3269 is_repl_pp
(PrunedPackage elab _
) = not (null (elabReplTarget elab
))
3271 -- Anything which is inplace and left after pruning could be a repl target, then just need to check the
3272 -- reverse closure after calculating roots to capture dependencies which are on the path between roots.
3273 -- In order to start a multi-repl session with all the desired targets we need to load all these components into
3274 -- the repl at once to satisfy the closure property.
3275 all_desired_repl_targets
= Set
.fromList
[elabUnitId cp | InstallPlan
.Configured cp
<- fromMaybe [] $ Graph
.revClosure closed_graph roots
]
3277 add_repl_target
:: ElaboratedConfiguredPackage
-> ElaboratedConfiguredPackage
3279 | elabUnitId ecp `Set
.member` all_desired_repl_targets
=
3281 { elabReplTarget
= maybeToList (ComponentTarget
<$> (elabComponentName ecp
) <*> pure WholeComponent
)
3282 , elabBuildStyle
= BuildInplaceOnly InMemory
3286 -- Add the repl target information to the ElaboratedPlanPackages
3287 graph_with_repl_targets
3288 | anyReplTarget
= map (mapConfiguredPackage add_repl_target
) (Graph
.toList closed_graph
)
3289 |
otherwise = Graph
.toList closed_graph
3291 -- But check that all the InMemory targets have a new enough version of Cabal,
3292 -- otherwise we will confuse Setup.hs by passing new arguments which it doesn't understand
3293 -- later down the line. We try to remove just these edges, if it doesn't break the overall structure
3294 -- then we just report to the user that their target will not be loaded for this reason.
3296 -- 'bad' are the nodes with a too old version of Cabal
3297 -- 'good' are the nodes with a new-enough version of Cabal
3298 (bad
, _good
) = partitionEithers
(map go graph_with_repl_targets
)
3300 go
:: ElaboratedPlanPackage
-> Either UnitId ElaboratedPlanPackage
3301 go
(InstallPlan
.Configured cp
)
3302 | BuildInplaceOnly InMemory
<- elabBuildStyle cp
3303 , elabSetupScriptCliVersion cp
< minVersionReplFlagFile
=
3304 Left
(elabUnitId cp
)
3305 go
(InstallPlan
.Configured c
) = Right
(InstallPlan
.Configured c
)
3308 -- Now take the upwards closure from the bad nodes, and find the other `BuildInplaceOnly InMemory` packages that clobbers,
3309 -- disables those and issue a warning to the user. Because we aren't going to be able to load those into memory as well
3310 -- because the thing it depends on is not going to be in memory.
3311 disabled_repl_targets
=
3312 [ c | InstallPlan
.Configured c
<- fromMaybe [] $ Graph
.revClosure
(Graph
.fromDistinctList graph_with_repl_targets
) bad
, BuildInplaceOnly InMemory
<- [elabBuildStyle c
]
3315 remove_repl_target
:: ElaboratedConfiguredPackage
-> ElaboratedConfiguredPackage
3316 remove_repl_target ecp
3317 | ecp `
elem` disabled_repl_targets
=
3319 { elabReplTarget
= []
3320 , elabBuildStyle
= BuildInplaceOnly OnDisk
3324 final_graph_with_repl_targets
= map (mapConfiguredPackage remove_repl_target
) graph_with_repl_targets
3326 -- Now find what the new roots are after we have disabled things which we can't build (and the things above that)
3327 new_roots
:: [UnitId
]
3328 new_roots
= mapMaybe find_root
(map (mapConfiguredPackage prune
) final_graph_with_repl_targets
)
3330 -- Then take the final closure from these new roots to remove these things
3331 -- TODO: Can probably just remove them directly in remove_repl_target.
3332 final_final_graph
= fromMaybe [] $ Graph
.closure
(Graph
.fromDistinctList final_graph_with_repl_targets
) new_roots
3334 is_root
:: PrunedPackage
-> Maybe UnitId
3335 is_root
(PrunedPackage elab _
) =
3338 [ null (elabConfigureTargets elab
)
3339 , null (elabBuildTargets elab
)
3340 , null (elabTestTargets elab
)
3341 , null (elabBenchTargets elab
)
3342 , null (elabReplTarget elab
)
3343 , null (elabHaddockTargets elab
)
3345 then Just
(installedUnitId elab
)
3348 find_root
(InstallPlan
.Configured pkg
) = is_root pkg
3349 -- When using the extra-packages stanza we need to
3350 -- look at installed packages as well.
3351 find_root
(InstallPlan
.Installed pkg
) = is_root pkg
3352 find_root _
= Nothing
3354 -- Note [Sticky enabled testsuites]
3355 -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
3356 -- The testsuite and benchmark targets are somewhat special in that we need
3357 -- to configure the packages with them enabled, and we need to do that even
3358 -- if we only want to build one of several testsuites.
3360 -- There are two cases in which we will enable the testsuites (or
3361 -- benchmarks): if one of the targets is a testsuite, or if all of the
3362 -- testsuite dependencies are already cached in the store. The rationale
3363 -- for the latter is to minimise how often we have to reconfigure due to
3364 -- the particular targets we choose to build. Otherwise choosing to build
3365 -- a testsuite target, and then later choosing to build an exe target
3366 -- would involve unnecessarily reconfiguring the package with testsuites
3367 -- disabled. Technically this introduces a little bit of stateful
3368 -- behaviour to make this "sticky", but it should be benign.
3370 -- Decide whether or not to enable testsuites and benchmarks.
3371 -- See [Sticky enabled testsuites]
3372 addOptionalStanzas
:: ElaboratedConfiguredPackage
-> ElaboratedConfiguredPackage
3373 addOptionalStanzas elab
@ElaboratedConfiguredPackage
{elabPkgOrComp
= ElabPackage pkg
} =
3375 { elabPkgOrComp
= ElabPackage
(pkg
{pkgStanzasEnabled
= stanzas
})
3378 stanzas
:: OptionalStanzaSet
3379 -- By default, we enabled all stanzas requested by the user,
3380 -- as per elabStanzasRequested, done in
3381 -- 'elaborateSolverToPackage'
3383 pkgStanzasEnabled pkg
3384 -- optionalStanzasRequiredByTargets has to be done at
3385 -- prune-time because it depends on 'elabTestTargets'
3386 -- et al, which is done by 'setRootTargets' at the
3387 -- beginning of pruning.
3388 <> optionalStanzasRequiredByTargets elab
3389 -- optionalStanzasWithDepsAvailable has to be done at
3390 -- prune-time because it depends on what packages are
3391 -- installed, which is not known until after improvement
3392 -- (pruning is done after improvement)
3393 <> optionalStanzasWithDepsAvailable availablePkgs elab pkg
3394 addOptionalStanzas elab
= elab
3396 -- Calculate package dependencies but cut out those needed only by
3397 -- optional stanzas that we've determined we will not enable.
3398 -- These pruned deps are not persisted in this pass since they're based on
3399 -- the optional stanzas and we'll make further tweaks to the optional
3400 -- stanzas in the next pass.
3402 pruneOptionalDependencies
:: ElaboratedConfiguredPackage
-> [UnitId
]
3403 pruneOptionalDependencies elab
@ElaboratedConfiguredPackage
{elabPkgOrComp
= ElabComponent _
} =
3404 InstallPlan
.depends elab
-- no pruning
3405 pruneOptionalDependencies ElaboratedConfiguredPackage
{elabPkgOrComp
= ElabPackage pkg
} =
3406 (CD
.flatDeps
. CD
.filterDeps keepNeeded
) (pkgOrderDependencies pkg
)
3408 keepNeeded
(CD
.ComponentTest _
) _
= TestStanzas `optStanzaSetMember` stanzas
3409 keepNeeded
(CD
.ComponentBench _
) _
= BenchStanzas `optStanzaSetMember` stanzas
3410 keepNeeded _ _
= True
3411 stanzas
= pkgStanzasEnabled pkg
3413 optionalStanzasRequiredByTargets
3414 :: ElaboratedConfiguredPackage
3415 -> OptionalStanzaSet
3416 optionalStanzasRequiredByTargets pkg
=
3417 optStanzaSetFromList
3419 | ComponentTarget cname _
<-
3420 elabBuildTargets pkg
3421 ++ elabTestTargets pkg
3422 ++ elabBenchTargets pkg
3423 ++ elabReplTarget pkg
3424 ++ elabHaddockTargets pkg
3427 componentOptionalStanza
$
3428 CD
.componentNameToComponent cname
3433 [ installedUnitId pkg
3434 | InstallPlan
.PreExisting pkg
<- pkgs
3438 Note [Pruning for Multi Repl]
3439 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
3441 For a multi-repl session, where we load more than one component into a GHCi repl,
3442 it is required to uphold the so-called *closure property*.
3443 This property, whose exact Note you can read in the GHC codebase, states
3446 \* If a component you want to load into a repl session transitively depends on a
3447 component which transitively depends on another component you want to
3448 load into the repl, then this component needs to be loaded
3449 into the repl session as well.
3451 We make sure here, that this property is upheld, by calculating the
3452 graph of components that we need to load into the repl given the set of 'roots' which
3453 are the targets specified by the user.
3455 Practically, this is simply achieved by traversing all dependencies of
3456 our roots (graph closure), and then from this closed graph, we calculate
3457 the reverse closure, which gives us all components that depend on
3458 'roots'. Thus, the result is a list of components that we need to load
3459 into the repl to uphold the closure property.
3461 Further to this, we then check that all the enabled components are using a new enough
3462 version of Cabal which understands the repl option to write the arguments to a file.
3464 If there is a package using a custom Setup.hs which is linked against a too old version
3465 of Cabal then we need to disable that as otherwise we will end up passing unknown
3466 arguments to `./Setup`.
3469 -- | Given a set of already installed packages @availablePkgs@,
3470 -- determine the set of available optional stanzas from @pkg@
3471 -- which have all of their dependencies already installed. This is used
3472 -- to implement "sticky" testsuites, where once we have installed
3473 -- all of the deps needed for the test suite, we go ahead and
3474 -- enable it always.
3475 optionalStanzasWithDepsAvailable
3477 -> ElaboratedConfiguredPackage
3478 -> ElaboratedPackage
3479 -> OptionalStanzaSet
3480 optionalStanzasWithDepsAvailable availablePkgs elab pkg
=
3481 optStanzaSetFromList
3483 | stanza
<- optStanzaSetToList
(elabStanzasAvailable elab
)
3484 , let deps
:: [UnitId
]
3487 (optionalStanzaDeps stanza
)
3488 -- TODO: probably need to select other
3489 -- dep types too eventually
3490 (pkgOrderDependencies pkg
)
3491 , all (`Set
.member` availablePkgs
) deps
3494 optionalStanzaDeps TestStanzas
(CD
.ComponentTest _
) = True
3495 optionalStanzaDeps BenchStanzas
(CD
.ComponentBench _
) = True
3496 optionalStanzaDeps _ _
= False
3498 -- The second pass does three things:
3501 -- * A second go at deciding which optional stanzas to enable.
3503 -- * Prune the dependencies based on the final choice of optional stanzas.
3505 -- * Extend the targets within each package to build, now we know the reverse
3507 -- dependencies, ie we know which libs are needed as deps by other packages.
3509 -- Achieving sticky behaviour with enabling\/disabling optional stanzas is
3510 -- tricky. The first approximation was handled by the first pass above, but
3511 -- it's not quite enough. That pass will enable stanzas if all of the deps
3512 -- of the optional stanza are already installed /in the store/. That's important
3513 -- but it does not account for dependencies that get built inplace as part of
3514 -- the project. We cannot take those inplace build deps into account in the
3515 -- pruning pass however because we don't yet know which ones we're going to
3516 -- build. Once we do know, we can have another go and enable stanzas that have
3517 -- all their deps available. Now we can consider all packages in the pruned
3518 -- plan to be available, including ones we already decided to build from
3521 -- Deciding which targets to build depends on knowing which packages have
3522 -- reverse dependencies (ie are needed). This requires the result of first
3523 -- pass, which is another reason we have to split it into two passes.
3525 -- Note that just because we might enable testsuites or benchmarks (in the
3526 -- first or second pass) doesn't mean that we build all (or even any) of them.
3527 -- That depends on which targets we picked in the first pass.
3529 pruneInstallPlanPass2
3530 :: [ElaboratedPlanPackage
]
3531 -> [ElaboratedPlanPackage
]
3532 pruneInstallPlanPass2 pkgs
=
3533 map (mapConfiguredPackage setStanzasDepsAndTargets
) pkgs
3535 setStanzasDepsAndTargets elab
=
3537 { elabBuildTargets
=
3539 elabBuildTargets elab
3540 ++ libTargetsRequiredForRevDeps
3541 ++ exeTargetsRequiredForRevDeps
3543 case elabPkgOrComp elab
of
3546 pkgStanzasEnabled pkg
3547 <> optionalStanzasWithDepsAvailable availablePkgs elab pkg
3549 keepNeeded
:: CD
.Component
-> a
-> Bool
3550 keepNeeded
(CD
.ComponentTest _
) _
= TestStanzas `optStanzaSetMember` stanzas
3551 keepNeeded
(CD
.ComponentBench _
) _
= BenchStanzas `optStanzaSetMember` stanzas
3552 keepNeeded _ _
= True
3555 { pkgStanzasEnabled
=
3557 , pkgLibDependencies
=
3558 CD
.mapDeps
(\_
-> map addInternal
) $
3559 CD
.filterDeps keepNeeded
(pkgLibDependencies pkg
)
3560 , pkgExeDependencies
=
3561 CD
.filterDeps keepNeeded
(pkgExeDependencies pkg
)
3562 , pkgExeDependencyPaths
=
3563 CD
.filterDeps keepNeeded
(pkgExeDependencyPaths pkg
)
3565 ElabComponent comp
->
3568 { compLibDependencies
= map addInternal
(compLibDependencies comp
)
3572 -- We initially assume that all the dependencies are external (hence the boolean is always
3573 -- False) and here we correct the dependencies so the right packages are marked promised.
3574 addInternal
(cid
, _
) = (cid
, (cid `Set
.member` inMemoryTargets
))
3576 libTargetsRequiredForRevDeps
=
3578 | installedUnitId elab `Set
.member` hasReverseLibDeps
3579 , let c
= ComponentTarget
(CLibName Cabal
.defaultLibName
) WholeComponent
3580 , -- Don't enable building for anything which is being build in memory
3581 elabBuildStyle elab
/= BuildInplaceOnly InMemory
3583 exeTargetsRequiredForRevDeps
=
3584 -- TODO: allow requesting executable with different name
3585 -- than package name
3588 packageNameToUnqualComponentName
$
3590 elabPkgSourceId elab
3593 | installedUnitId elab `Set
.member` hasReverseExeDeps
3596 availablePkgs
:: Set UnitId
3597 availablePkgs
= Set
.fromList
(map installedUnitId pkgs
)
3599 inMemoryTargets
:: Set ConfiguredId
3600 inMemoryTargets
= do
3603 | InstallPlan
.Configured pkg
<- pkgs
3604 , BuildInplaceOnly InMemory
<- [elabBuildStyle pkg
]
3607 hasReverseLibDeps
:: Set UnitId
3611 | InstallPlan
.Configured pkg
<- pkgs
3612 , depid
<- elabOrderLibDependencies pkg
3615 hasReverseExeDeps
:: Set UnitId
3619 | InstallPlan
.Configured pkg
<- pkgs
3620 , depid
<- elabOrderExeDependencies pkg
3623 mapConfiguredPackage
3624 :: (srcpkg
-> srcpkg
')
3625 -> InstallPlan
.GenericPlanPackage ipkg srcpkg
3626 -> InstallPlan
.GenericPlanPackage ipkg srcpkg
'
3627 mapConfiguredPackage f
(InstallPlan
.Configured pkg
) =
3628 InstallPlan
.Configured
(f pkg
)
3629 mapConfiguredPackage f
(InstallPlan
.Installed pkg
) =
3630 InstallPlan
.Installed
(f pkg
)
3631 mapConfiguredPackage _
(InstallPlan
.PreExisting pkg
) =
3632 InstallPlan
.PreExisting pkg
3634 ------------------------------------
3635 -- Support for --only-dependencies
3638 -- | Try to remove the given targets from the install plan.
3640 -- This is not always possible.
3641 pruneInstallPlanToDependencies
3643 -> ElaboratedInstallPlan
3645 CannotPruneDependencies
3646 ElaboratedInstallPlan
3647 pruneInstallPlanToDependencies pkgTargets installPlan
=
3650 (isJust . InstallPlan
.lookup installPlan
)
3651 (Set
.toList pkgTargets
)
3653 $ fmap (InstallPlan
.new
(InstallPlan
.planIndepGoals installPlan
))
3655 . Graph
.fromDistinctList
3656 . filter (\pkg
-> installedUnitId pkg `Set
.notMember` pkgTargets
)
3657 . InstallPlan
.toList
3660 -- Our strategy is to remove the packages we don't want and then check
3661 -- if the remaining graph is broken or not, ie any packages with dangling
3662 -- dependencies. If there are then we cannot prune the given targets.
3664 :: Graph
.Graph ElaboratedPlanPackage
3666 CannotPruneDependencies
3667 (Graph
.Graph ElaboratedPlanPackage
)
3668 checkBrokenDeps graph
=
3669 case Graph
.broken graph
of
3673 CannotPruneDependencies
3674 [ (pkg
, missingDeps
)
3675 |
(pkg
, missingDepIds
) <- brokenPackages
3676 , let missingDeps
= mapMaybe lookupDep missingDepIds
3679 -- lookup in the original unpruned graph
3680 lookupDep
= InstallPlan
.lookup installPlan
3682 -- | It is not always possible to prune to only the dependencies of a set of
3683 -- targets. It may be the case that removing a package leaves something else
3684 -- that still needed the pruned package.
3686 -- This lists all the packages that would be broken, and their dependencies
3687 -- that would be missing if we did prune.
3688 newtype CannotPruneDependencies
3689 = CannotPruneDependencies
3690 [ ( ElaboratedPlanPackage
3691 , [ElaboratedPlanPackage
]
3696 -- The other aspects of our Setup.hs policy lives here where we decide on
3697 -- the 'SetupScriptOptions'.
3699 -- Our current policy for the 'SetupCustomImplicitDeps' case is that we
3700 -- try to make the implicit deps cover everything, and we don't allow the
3701 -- compiler to pick up other deps. This may or may not be sustainable, and
3702 -- we might have to allow the deps to be non-exclusive, but that itself would
3703 -- be tricky since we would have to allow the Setup access to all the packages
3704 -- in the store and local dbs.
3706 setupHsScriptOptions
3707 :: ElaboratedReadyPackage
3708 -> ElaboratedInstallPlan
3709 -> ElaboratedSharedConfig
3715 -> SetupScriptOptions
3716 -- TODO: Fix this so custom is a separate component. Custom can ALWAYS
3717 -- be a separate component!!!
3718 setupHsScriptOptions
3719 (ReadyPackage elab
@ElaboratedConfiguredPackage
{..})
3721 ElaboratedSharedConfig
{..}
3728 { useCabalVersion
= thisVersion elabSetupScriptCliVersion
3729 , useCabalSpecVersion
= Just elabSetupScriptCliVersion
3730 , useCompiler
= Just pkgConfigCompiler
3731 , usePlatform
= Just pkgConfigPlatform
3732 , usePackageDB
= elabSetupPackageDBStack
3733 , usePackageIndex
= Nothing
3736 |
(ConfiguredId srcid
(Just
(CLibName LMainLibName
)) uid
, _
) <-
3737 elabSetupDependencies elab
3739 , useDependenciesExclusive
= True
3740 , useVersionMacros
= elabSetupScriptStyle
== SetupCustomExplicitDeps
3741 , useProgramDb
= pkgConfigCompilerProgs
3742 , useDistPref
= builddir
3743 , useLoggingHandle
= Nothing
-- this gets set later
3744 , useWorkingDir
= Just srcdir
3745 , useExtraPathEnv
= elabExeDependencyPaths elab
++ elabProgramPathExtra
3746 , -- note that the above adds the extra-prog-path directly following the elaborated
3747 -- dep paths, so that it overrides the normal path, but _not_ the elaborated extensions
3748 -- for build-tools-depends.
3749 useExtraEnvOverrides
= dataDirsEnvironmentForPlan distdir plan
3750 , useWin32CleanHack
= False -- TODO: [required eventually]
3751 , forceExternalSetupMethod
= isParallelBuild
3752 , setupCacheLock
= Just cacheLock
3753 , isInteractive
= False
3756 -- | To be used for the input for elaborateInstallPlan.
3758 -- TODO: [code cleanup] make InstallDirs.defaultInstallDirs pure.
3759 userInstallDirTemplates
3761 -> IO InstallDirs
.InstallDirTemplates
3762 userInstallDirTemplates compiler
= do
3763 InstallDirs
.defaultInstallDirs
3764 (compilerFlavor compiler
)
3765 True -- user install
3768 storePackageInstallDirs
3771 -> InstalledPackageId
3772 -> InstallDirs
.InstallDirs
FilePath
3773 storePackageInstallDirs storeDirLayout compid ipkgid
=
3774 storePackageInstallDirs
' storeDirLayout compid
$ newSimpleUnitId ipkgid
3776 storePackageInstallDirs
'
3780 -> InstallDirs
.InstallDirs
FilePath
3781 storePackageInstallDirs
'
3783 { storePackageDirectory
3788 InstallDirs
.InstallDirs
{..}
3790 store
= storeDirectory compid
3791 prefix
= storePackageDirectory compid unitid
3792 bindir
= prefix
</> "bin"
3793 libdir
= prefix
</> "lib"
3795 -- Note: on macOS, we place libraries into
3796 -- @store/lib@ to work around the load
3797 -- command size limit of macOSs mach-o linker.
3798 -- See also @PackageHash.hashedInstalledPackageIdVeryShort@
3800 | buildOS
== OSX
= store
</> "lib"
3801 |
otherwise = libdir
3803 libexecdir
= prefix
</> "libexec"
3805 includedir
= libdir
</> "include"
3806 datadir
= prefix
</> "share"
3808 docdir
= datadir
</> "doc"
3809 mandir
= datadir
</> "man"
3810 htmldir
= docdir
</> "html"
3811 haddockdir
= htmldir
3812 sysconfdir
= prefix
</> "etc"
3816 -> InstallDirs
.InstallDirTemplates
3817 -> ElaboratedSharedConfig
3818 -> ElaboratedConfiguredPackage
3819 -> InstallDirs
.InstallDirs
FilePath
3820 computeInstallDirs storeDirLayout defaultInstallDirs elaboratedShared elab
3821 | isInplaceBuildStyle
(elabBuildStyle elab
) =
3822 -- use the ordinary default install dirs
3823 ( InstallDirs
.absoluteInstallDirs
3824 (elabPkgSourceId elab
)
3826 (compilerInfo
(pkgConfigCompiler elaboratedShared
))
3827 InstallDirs
.NoCopyDest
3828 (pkgConfigPlatform elaboratedShared
)
3831 { -- absoluteInstallDirs sets these as 'undefined' but we have
3832 -- to use them as "Setup.hs configure" args
3833 InstallDirs
.libsubdir
= ""
3834 , InstallDirs
.libexecsubdir
= ""
3835 , InstallDirs
.datasubdir
= ""
3838 -- use special simplified install dirs
3839 storePackageInstallDirs
'
3841 (compilerId
(pkgConfigCompiler elaboratedShared
))
3844 -- TODO: [code cleanup] perhaps reorder this code
3845 -- based on the ElaboratedInstallPlan + ElaboratedSharedConfig,
3846 -- make the various Setup.hs {configure,build,copy} flags
3848 setupHsConfigureFlags
3849 :: ElaboratedInstallPlan
3850 -> ElaboratedReadyPackage
3851 -> ElaboratedSharedConfig
3854 -> Cabal
.ConfigFlags
3855 setupHsConfigureFlags
3857 (ReadyPackage elab
@ElaboratedConfiguredPackage
{..})
3858 sharedConfig
@ElaboratedSharedConfig
{..}
3861 sanityCheckElaboratedConfiguredPackage
3864 (Cabal
.ConfigFlags
{..})
3866 configArgs
= mempty
-- unused, passed via args
3867 configDistPref
= toFlag builddir
3868 configCabalFilePath
= mempty
3869 configVerbosity
= toFlag verbosity
3871 configInstantiateWith
= Map
.toList elabInstantiatedWith
3873 configDeterministic
= mempty
-- doesn't matter, configIPID/configCID overridese
3874 configIPID
= case elabPkgOrComp
of
3875 ElabPackage pkg
-> toFlag
(prettyShow
(pkgInstalledId pkg
))
3876 ElabComponent _
-> mempty
3877 configCID
= case elabPkgOrComp
of
3878 ElabPackage _
-> mempty
3879 ElabComponent _
-> toFlag elabComponentId
3881 configProgramPaths
= Map
.toList elabProgramPaths
3883 |
{- elabSetupScriptCliVersion < mkVersion [1,24,3] -} True =
3884 -- workaround for <https://github.com/haskell/cabal/issues/4010>
3886 -- It turns out, that even with Cabal 2.0, there's still cases such as e.g.
3887 -- custom Setup.hs scripts calling out to GHC even when going via
3888 -- @runProgram ghcProgram@, as e.g. happy does in its
3889 -- <http://hackage.haskell.org/package/happy-1.19.5/src/Setup.lhs>
3890 -- (see also <https://github.com/haskell/cabal/pull/4433#issuecomment-299396099>)
3892 -- So for now, let's pass the rather harmless and idempotent
3893 -- `-hide-all-packages` flag to all invocations (which has
3894 -- the benefit that every GHC invocation starts with a
3895 -- consistently well-defined clean slate) until we find a
3901 ["-hide-all-packages"]
3903 configProgramPathExtra
= toNubList elabProgramPathExtra
3904 configHcFlavor
= toFlag
(compilerFlavor pkgConfigCompiler
)
3905 configHcPath
= mempty
-- we use configProgramPaths instead
3906 configHcPkg
= mempty
-- we use configProgramPaths instead
3907 configVanillaLib
= toFlag elabVanillaLib
3908 configSharedLib
= toFlag elabSharedLib
3909 configStaticLib
= toFlag elabStaticLib
3911 configDynExe
= toFlag elabDynExe
3912 configFullyStaticExe
= toFlag elabFullyStaticExe
3913 configGHCiLib
= toFlag elabGHCiLib
3914 configProfExe
= mempty
3915 configProfLib
= toFlag elabProfLib
3916 configProf
= toFlag elabProfExe
3918 -- configProfDetail is for exe+lib, but overridden by configProfLibDetail
3919 -- so we specify both so we can specify independently
3920 configProfDetail
= toFlag elabProfExeDetail
3921 configProfLibDetail
= toFlag elabProfLibDetail
3923 configCoverage
= toFlag elabCoverage
3924 configLibCoverage
= mempty
3926 configOptimization
= toFlag elabOptimization
3927 configSplitSections
= toFlag elabSplitSections
3928 configSplitObjs
= toFlag elabSplitObjs
3929 configStripExes
= toFlag elabStripExes
3930 configStripLibs
= toFlag elabStripLibs
3931 configDebugInfo
= toFlag elabDebugInfo
3932 configDumpBuildInfo
= toFlag elabDumpBuildInfo
3934 configConfigurationsFlags
= elabFlagAssignment
3935 configConfigureArgs
= elabConfigureScriptArgs
3936 configExtraLibDirs
= elabExtraLibDirs
3937 configExtraLibDirsStatic
= elabExtraLibDirsStatic
3938 configExtraFrameworkDirs
= elabExtraFrameworkDirs
3939 configExtraIncludeDirs
= elabExtraIncludeDirs
3940 configProgPrefix
= maybe mempty toFlag elabProgPrefix
3941 configProgSuffix
= maybe mempty toFlag elabProgSuffix
3945 (toFlag
. InstallDirs
.toPathTemplate
)
3948 -- we only use configDependencies, unless we're talking to an old Cabal
3949 -- in which case we use configConstraints
3950 -- NB: This does NOT use InstallPlan.depends, which includes executable
3951 -- dependencies which should NOT be fed in here (also you don't have
3952 -- enough info anyway)
3954 configDependencies
=
3955 [ cidToGivenComponent cid
3956 |
(cid
, is_internal
) <- elabLibDependencies elab
3960 configPromisedDependencies
=
3961 [ cidToGivenComponent cid
3962 |
(cid
, is_internal
) <- elabLibDependencies elab
3967 case elabPkgOrComp
of
3969 [ thisPackageVersionConstraint srcid
3970 |
(ConfiguredId srcid _ _uid
, _
) <- elabLibDependencies elab
3972 ElabComponent _
-> []
3974 -- explicitly clear, then our package db stack
3975 -- TODO: [required eventually] have to do this differently for older Cabal versions
3976 configPackageDBs
= Nothing
: map Just elabBuildPackageDBStack
3978 configTests
= case elabPkgOrComp
of
3979 ElabPackage pkg
-> toFlag
(TestStanzas `optStanzaSetMember` pkgStanzasEnabled pkg
)
3980 ElabComponent _
-> mempty
3981 configBenchmarks
= case elabPkgOrComp
of
3982 ElabPackage pkg
-> toFlag
(BenchStanzas `optStanzaSetMember` pkgStanzasEnabled pkg
)
3983 ElabComponent _
-> mempty
3985 configExactConfiguration
= toFlag
True
3986 configFlagError
= mempty
-- TODO: [research required] appears not to be implemented
3987 configRelocatable
= mempty
-- TODO: [research required] ???
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
3998 Just
(CLibName lname
) -> lname
3999 Just _
-> error "non-library dependency"
4000 Nothing
-> LMainLibName
4002 configCoverageFor
= determineCoverageFor elabPkgSourceId plan
4004 setupHsConfigureArgs
4005 :: ElaboratedConfiguredPackage
4007 setupHsConfigureArgs
(ElaboratedConfiguredPackage
{elabPkgOrComp
= ElabPackage _
}) = []
4008 setupHsConfigureArgs elab
@(ElaboratedConfiguredPackage
{elabPkgOrComp
= ElabComponent comp
}) =
4009 [showComponentTarget
(packageId elab
) (ComponentTarget cname WholeComponent
)]
4013 (error "setupHsConfigureArgs: trying to configure setup")
4014 (compComponentName comp
)
4018 -> ElaboratedConfiguredPackage
4019 -> ElaboratedSharedConfig
4023 setupHsBuildFlags par_strat elab _ verbosity builddir
=
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
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
)
4046 setupHsBuildArgs
(ElaboratedConfiguredPackage
{elabPkgOrComp
= ElabComponent _
}) =
4050 :: ElaboratedConfiguredPackage
4054 setupHsTestFlags
(ElaboratedConfiguredPackage
{..}) verbosity builddir
=
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
)
4073 :: ElaboratedConfiguredPackage
4074 -> ElaboratedSharedConfig
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
)
4090 :: ElaboratedConfiguredPackage
4091 -> ElaboratedSharedConfig
4095 setupHsReplFlags _ sharedConfig verbosity builddir
=
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
)
4110 :: ElaboratedConfiguredPackage
4111 -> ElaboratedSharedConfig
4116 setupHsCopyFlags _ _ verbosity builddir destdir
=
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
4131 -> Cabal
.RegisterFlags
4132 setupHsRegisterFlags
4133 ElaboratedConfiguredPackage
{..}
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
4148 , regVerbosity
= toFlag verbosity
4149 , regCabalFilePath
= mempty
4153 :: ElaboratedConfiguredPackage
4154 -> ElaboratedSharedConfig
4157 -> Cabal
.HaddockFlags
4158 setupHsHaddockFlags
(ElaboratedConfiguredPackage
{..}) (ElaboratedSharedConfig
{..}) verbosity builddir
=
4160 { haddockProgramPaths
=
4161 case lookupProgram haddockProgram pkgConfigCompilerProgs
of
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.
4245 :: ElaboratedSharedConfig
4246 -> ElaboratedConfiguredPackage
4247 -> PackageHashInputs
4250 elab
@( ElaboratedConfiguredPackage
4251 { elabPkgSourceHash
= Just srchash
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
{..}) ->
4267 |
(dep
, _
) <- CD
.select relevantDeps pkgLibDependencies
4270 | dep
<- CD
.select relevantDeps pkgExeDependencies
4272 ElabComponent comp
->
4276 ( map fst (compLibDependencies comp
)
4277 ++ compExeDependencies comp
4280 , pkgHashOtherConfig
= packageHashConfigInputs pkgshared elab
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
=
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
= elabVanillaLib
4310 , pkgHashSharedLib
= elabSharedLib
4311 , pkgHashDynExe
= elabDynExe
4312 , pkgHashFullyStaticExe
= elabFullyStaticExe
4313 , pkgHashGHCiLib
= elabGHCiLib
4314 , pkgHashProfLib
= elabProfLib
4315 , pkgHashProfExe
= elabProfExe
4316 , pkgHashProfLibDetail
= elabProfLibDetail
4317 , pkgHashProfExeDetail
= elabProfExeDetail
4318 , pkgHashCoverage
= elabCoverage
4319 , pkgHashOptimization
= elabOptimization
4320 , pkgHashSplitSections
= elabSplitSections
4321 , pkgHashSplitObjs
= elabSplitObjs
4322 , pkgHashStripLibs
= elabStripLibs
4323 , pkgHashStripExes
= elabStripExes
4324 , pkgHashDebugInfo
= elabDebugInfo
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
4352 ElaboratedConfiguredPackage
{..} = normaliseConfiguredPackage shared pkg
4354 -- | Given the 'InstalledPackageIndex' for a nix-style package store, and an
4355 -- 'ElaboratedInstallPlan', replace configured source packages by installed
4356 -- packages from the store whenever they exist.
4357 improveInstallPlanWithInstalledPackages
4359 -> ElaboratedInstallPlan
4360 -> ElaboratedInstallPlan
4361 improveInstallPlanWithInstalledPackages installedPkgIdSet
=
4362 InstallPlan
.installed canPackageBeImproved
4364 canPackageBeImproved pkg
=
4365 installedUnitId pkg `Set
.member` installedPkgIdSet
4367 -- TODO: sanity checks:
4368 -- \* the installed package must have the expected deps etc
4369 -- \* the installed package must not be broken, valid dep closure
4371 -- TODO: decide what to do if we encounter broken installed packages,
4372 -- since overwriting is never safe.
4374 -- Path construction
4377 -- | The path to the directory that contains a specific executable.
4378 -- NB: For inplace NOT InstallPaths.bindir installDirs; for an
4379 -- inplace build those values are utter nonsense. So we
4380 -- have to guess where the directory is going to be.
4381 -- Fortunately this is "stable" part of Cabal API.
4382 -- But the way we get the build directory is A HORRIBLE
4386 -> ElaboratedSharedConfig
4387 -> ElaboratedConfiguredPackage
4390 binDirectoryFor layout config package exe
= case elabBuildStyle package
of
4391 BuildAndInstall
-> installedBinDirectory package
4392 BuildInplaceOnly
{} -> inplaceBinRoot layout config package
</> exe
4394 -- package has been built and installed.
4395 installedBinDirectory
:: ElaboratedConfiguredPackage
-> FilePath
4396 installedBinDirectory
= InstallDirs
.bindir
. elabInstallDirs
4398 -- | The path to the @build@ directory for an inplace build.
4401 -> ElaboratedSharedConfig
4402 -> ElaboratedConfiguredPackage
4404 inplaceBinRoot layout config package
=
4405 distBuildDirectory layout
(elabDistDirParams config package
)
4408 --------------------------------------------------------------------------------
4409 -- Configure --coverage-for flags
4411 -- The list of non-pre-existing libraries without module holes, i.e. the
4412 -- main library and sub-libraries components of all the local packages in
4413 -- the project that do not require instantiations or are instantiations.
4414 determineCoverageFor
4416 -- ^ The 'PackageId' of the package or component being configured
4417 -> ElaboratedInstallPlan
4419 determineCoverageFor configuredPkgSourceId plan
=
4423 InstallPlan
.Installed elab
4424 | shouldCoverPkg elab
-> Just
$ elabUnitId elab
4425 InstallPlan
.Configured elab
4426 | shouldCoverPkg elab
-> Just
$ elabUnitId elab
4430 $ InstallPlan
.toGraph plan
4432 shouldCoverPkg elab
@ElaboratedConfiguredPackage
{elabModuleShape
, elabPkgSourceId
, elabLocalToProject
} =
4434 && not (isIndefiniteOrInstantiation elabModuleShape
)
4435 -- TODO(#9493): We can only cover libraries in the same package
4437 && configuredPkgSourceId
== elabPkgSourceId
4438 -- Libraries only! We don't cover testsuite modules, so we never need
4439 -- the paths to their mix dirs. Furthermore, we do not install testsuites...
4440 && maybe False (\case CLibName
{} -> True; CNotLibName
{} -> False) (elabComponentName elab
)
4442 isIndefiniteOrInstantiation
:: ModuleShape
-> Bool
4443 isIndefiniteOrInstantiation
= not . Set
.null . modShapeRequires