Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Elaborated: worked out with great care and nicety of detail; executed with great minuteness: elaborate preparations; elaborate care.
In this module we construct an install plan that includes all the information needed to execute it.
Building a project is therefore split into two phases:
- The construction of the install plan (which as far as possible should be pure), done here.
- The execution of the plan, done in ProjectBuilding
To achieve this we need a representation of this fully elaborated install plan; this representation consists of two parts:
- A
ElaboratedInstallPlan
. This is aGenericInstallPlan
with a representation of source packages that includes a lot more detail about that package's individual configuration - A
ElaboratedSharedConfig
. Some package configuration is the same for every package in a plan. Rather than duplicate that info every entry in theGenericInstallPlan
we keep that separately.
The division between the shared and per-package config is not set in stone for all time. For example if we wanted to generalise the install plan to describe a situation where we want to build some packages with GHC and some with GHCJS then the platform and compiler would no longer be shared between all packages but would have to be per-package (probably with some sanity condition on the graph structure).
Synopsis
- type ElaboratedInstallPlan = GenericInstallPlan InstalledPackageInfo ElaboratedConfiguredPackage
- data ElaboratedConfiguredPackage = ElaboratedConfiguredPackage {
- elabUnitId :: UnitId
- elabComponentId :: ComponentId
- elabInstantiatedWith :: Map ModuleName Module
- elabLinkedInstantiatedWith :: Map ModuleName OpenModule
- elabIsCanonical :: Bool
- elabPkgSourceId :: PackageId
- elabModuleShape :: ModuleShape
- elabFlagAssignment :: FlagAssignment
- elabFlagDefaults :: FlagAssignment
- elabPkgDescription :: PackageDescription
- elabPkgSourceLocation :: PackageLocation (Maybe FilePath)
- elabPkgSourceHash :: Maybe PackageSourceHash
- elabLocalToProject :: Bool
- elabBuildStyle :: BuildStyle
- elabEnabledSpec :: ComponentRequestedSpec
- elabStanzasAvailable :: OptionalStanzaSet
- elabStanzasRequested :: OptionalStanzaMap (Maybe Bool)
- elabPackageDbs :: [Maybe PackageDBCWD]
- elabSetupPackageDBStack :: PackageDBStackCWD
- elabBuildPackageDBStack :: PackageDBStackCWD
- elabRegisterPackageDBStack :: PackageDBStackCWD
- elabInplaceSetupPackageDBStack :: PackageDBStackCWD
- elabInplaceBuildPackageDBStack :: PackageDBStackCWD
- elabInplaceRegisterPackageDBStack :: PackageDBStackCWD
- elabPkgDescriptionOverride :: Maybe CabalFileText
- elabBuildOptions :: BuildOptions
- elabDumpBuildInfo :: DumpBuildInfo
- elabProgramPaths :: Map String FilePath
- elabProgramArgs :: Map String [String]
- elabProgramPathExtra :: [FilePath]
- elabConfigureScriptArgs :: [String]
- elabExtraLibDirs :: [FilePath]
- elabExtraLibDirsStatic :: [FilePath]
- elabExtraFrameworkDirs :: [FilePath]
- elabExtraIncludeDirs :: [FilePath]
- elabProgPrefix :: Maybe PathTemplate
- elabProgSuffix :: Maybe PathTemplate
- elabInstallDirs :: InstallDirs FilePath
- elabHaddockHoogle :: Bool
- elabHaddockHtml :: Bool
- elabHaddockHtmlLocation :: Maybe String
- elabHaddockForeignLibs :: Bool
- elabHaddockForHackage :: HaddockTarget
- elabHaddockExecutables :: Bool
- elabHaddockTestSuites :: Bool
- elabHaddockBenchmarks :: Bool
- elabHaddockInternal :: Bool
- elabHaddockCss :: Maybe FilePath
- elabHaddockLinkedSource :: Bool
- elabHaddockQuickJump :: Bool
- elabHaddockHscolourCss :: Maybe FilePath
- elabHaddockContents :: Maybe PathTemplate
- elabHaddockIndex :: Maybe PathTemplate
- elabHaddockBaseUrl :: Maybe String
- elabHaddockResourcesDir :: Maybe String
- elabHaddockOutputDir :: Maybe FilePath
- elabHaddockUseUnicode :: Bool
- elabTestMachineLog :: Maybe PathTemplate
- elabTestHumanLog :: Maybe PathTemplate
- elabTestShowDetails :: Maybe TestShowDetails
- elabTestKeepTix :: Bool
- elabTestWrapper :: Maybe FilePath
- elabTestFailWhenNoTestSuites :: Bool
- elabTestTestOptions :: [PathTemplate]
- elabBenchmarkOptions :: [PathTemplate]
- elabSetupScriptStyle :: SetupScriptStyle
- elabSetupScriptCliVersion :: Version
- elabConfigureTargets :: [ComponentTarget]
- elabBuildTargets :: [ComponentTarget]
- elabTestTargets :: [ComponentTarget]
- elabBenchTargets :: [ComponentTarget]
- elabReplTarget :: [ComponentTarget]
- elabHaddockTargets :: [ComponentTarget]
- elabBuildHaddocks :: Bool
- elabPkgOrComp :: ElaboratedPackageOrComponent
- type ElaboratedPlanPackage = GenericPlanPackage InstalledPackageInfo ElaboratedConfiguredPackage
- data ElaboratedSharedConfig = ElaboratedSharedConfig {}
- type ElaboratedReadyPackage = GenericReadyPackage ElaboratedConfiguredPackage
- data BuildStyle
- type CabalFileText = ByteString
- rebuildProjectConfig :: Verbosity -> HttpTransport -> DistDirLayout -> ProjectConfig -> IO (ProjectConfig, [PackageSpecifier UnresolvedSourcePackage])
- rebuildInstallPlan :: Verbosity -> DistDirLayout -> CabalDirLayout -> ProjectConfig -> [PackageSpecifier UnresolvedSourcePackage] -> Maybe InstalledPackageIndex -> IO (ElaboratedInstallPlan, ElaboratedInstallPlan, ElaboratedSharedConfig, TotalIndexState, ActiveRepos)
- availableTargets :: ElaboratedInstallPlan -> Map (PackageId, ComponentName) [AvailableTarget (UnitId, ComponentName)]
- data AvailableTarget k = AvailableTarget {}
- data AvailableTargetStatus k
- data TargetRequested
- data ComponentTarget = ComponentTarget ComponentName SubComponentTarget
- data SubComponentTarget
- showComponentTarget :: PackageId -> ComponentTarget -> String
- nubComponentTargets :: [(ComponentTarget, a)] -> [(ComponentTarget, NonEmpty a)]
- pruneInstallPlanToTargets :: TargetAction -> Map UnitId [ComponentTarget] -> ElaboratedInstallPlan -> ElaboratedInstallPlan
- data TargetAction
- pruneInstallPlanToDependencies :: Set UnitId -> ElaboratedInstallPlan -> Either CannotPruneDependencies ElaboratedInstallPlan
- newtype CannotPruneDependencies = CannotPruneDependencies [(ElaboratedPlanPackage, [ElaboratedPlanPackage])]
- pkgHasEphemeralBuildTargets :: ElaboratedConfiguredPackage -> Bool
- elabBuildTargetWholeComponents :: ElaboratedConfiguredPackage -> Set ComponentName
- configureCompiler :: Verbosity -> DistDirLayout -> ProjectConfig -> Rebuild (Compiler, Platform, ProgramDb)
- setupHsScriptOptions :: ElaboratedReadyPackage -> ElaboratedInstallPlan -> ElaboratedSharedConfig -> DistDirLayout -> SymbolicPath CWD (Dir Pkg) -> SymbolicPath Pkg (Dir Dist) -> Bool -> Lock -> SetupScriptOptions
- setupHsCommonFlags :: Verbosity -> Maybe (SymbolicPath CWD (Dir Pkg)) -> SymbolicPath Pkg (Dir Dist) -> CommonSetupFlags
- setupHsConfigureFlags :: Monad m => (FilePath -> m (SymbolicPath Pkg (Dir PkgDB))) -> ElaboratedInstallPlan -> ElaboratedReadyPackage -> ElaboratedSharedConfig -> CommonSetupFlags -> m ConfigFlags
- setupHsConfigureArgs :: ElaboratedConfiguredPackage -> [String]
- setupHsBuildFlags :: Flag String -> ElaboratedConfiguredPackage -> ElaboratedSharedConfig -> CommonSetupFlags -> BuildFlags
- setupHsBuildArgs :: ElaboratedConfiguredPackage -> [String]
- setupHsReplFlags :: ElaboratedConfiguredPackage -> ElaboratedSharedConfig -> CommonSetupFlags -> ReplFlags
- setupHsReplArgs :: ElaboratedConfiguredPackage -> [String]
- setupHsTestFlags :: ElaboratedConfiguredPackage -> CommonSetupFlags -> TestFlags
- setupHsTestArgs :: ElaboratedConfiguredPackage -> [String]
- setupHsBenchFlags :: ElaboratedConfiguredPackage -> ElaboratedSharedConfig -> CommonSetupFlags -> BenchmarkFlags
- setupHsBenchArgs :: ElaboratedConfiguredPackage -> [String]
- setupHsCopyFlags :: ElaboratedConfiguredPackage -> ElaboratedSharedConfig -> CommonSetupFlags -> FilePath -> CopyFlags
- setupHsRegisterFlags :: ElaboratedConfiguredPackage -> ElaboratedSharedConfig -> CommonSetupFlags -> FilePath -> RegisterFlags
- setupHsHaddockFlags :: ElaboratedConfiguredPackage -> ElaboratedSharedConfig -> BuildTimeSettings -> CommonSetupFlags -> HaddockFlags
- setupHsHaddockArgs :: ElaboratedConfiguredPackage -> [String]
- packageHashInputs :: ElaboratedSharedConfig -> ElaboratedConfiguredPackage -> PackageHashInputs
- binDirectoryFor :: DistDirLayout -> ElaboratedSharedConfig -> ElaboratedConfiguredPackage -> FilePath -> FilePath
- binDirectories :: DistDirLayout -> ElaboratedSharedConfig -> ElaboratedConfiguredPackage -> [FilePath]
- storePackageInstallDirs :: StoreDirLayout -> Compiler -> InstalledPackageId -> InstallDirs FilePath
- storePackageInstallDirs' :: StoreDirLayout -> Compiler -> UnitId -> InstallDirs FilePath
Types for the elaborated install plan
type ElaboratedInstallPlan = GenericInstallPlan InstalledPackageInfo ElaboratedConfiguredPackage Source #
The combination of an elaborated install plan plus a
ElaboratedSharedConfig
contains all the details necessary to be able
to execute the plan without having to make further policy decisions.
It does not include dynamic elements such as resources (such as http connections).
data ElaboratedConfiguredPackage Source #
ElaboratedConfiguredPackage | |
|
Instances
type ElaboratedPlanPackage = GenericPlanPackage InstalledPackageInfo ElaboratedConfiguredPackage Source #
data ElaboratedSharedConfig Source #
ElaboratedSharedConfig | |
|
Instances
data BuildStyle Source #
This is used in the install plan to indicate how the package will be built.
BuildAndInstall | The classic approach where the package is built, then the files installed into some location and the result registered in a package db. If the package came from a tarball then it's built in a temp dir and the results discarded. |
BuildInplaceOnly MemoryOrDisk | For Such packages can still subsequently be installed. Typically For At the moment We use single constructor |
Instances
type CabalFileText = ByteString Source #
Reading the project configuration
The project configuration is assembled into a ProjectConfig as follows:
CLI arguments are converted using "commandLineFlagsToProjectConfig" in the v2 command entrypoints and passed to "establishProjectBaseContext" which then calls "rebuildProjectConfig".
"rebuildProjectConfig" then calls "readProjectConfig" to read the project files. Due to the presence of conditionals, this output is in the form of a ProjectConfigSkeleton and will be resolved by "rebuildProjectConfig" using "instantiateProjectConfigSkeletonFetchingCompiler".
"readProjectConfig" also loads the global configuration, which is read with "loadConfig" and convertd to a ProjectConfig with "convertLegacyGlobalConfig".
- Important:* You can notice how some project config options are needed to read the project config! This is evident by the fact that "rebuildProjectConfig" takes HttpTransport and DistDirLayout as parameters. Two arguments are infact determined from the CLI alone (in "establishProjectBaseContext"). Consequently, project files (including global configuration) cannot affect those parameters!
Furthermore, the project configuration can specify a compiler to use, which we need to resolve the conditionals in the project configuration! To solve this, we configure the compiler from what is obtained by applying the CLI configuration over the the configuration obtained by "flattening" ProjectConfigSkeleton. This means collapsing all conditionals by taking both branches.
rebuildProjectConfig :: Verbosity -> HttpTransport -> DistDirLayout -> ProjectConfig -> IO (ProjectConfig, [PackageSpecifier UnresolvedSourcePackage]) Source #
Return the up-to-date project config and information about the local packages within the project.
Producing the elaborated install plan
:: Verbosity | |
-> DistDirLayout | |
-> CabalDirLayout | |
-> ProjectConfig | |
-> [PackageSpecifier UnresolvedSourcePackage] | |
-> Maybe InstalledPackageIndex | |
-> IO (ElaboratedInstallPlan, ElaboratedInstallPlan, ElaboratedSharedConfig, TotalIndexState, ActiveRepos) | (improvedPlan, elaboratedPlan, _, _, _) |
Return an up-to-date elaborated install plan.
Two variants of the install plan are returned: with and without packages from the store. That is, the "improved" plan where source packages are replaced by pre-existing installed packages from the store (when their ids match), and also the original elaborated plan which uses primarily source packages.
Build targets
availableTargets :: ElaboratedInstallPlan -> Map (PackageId, ComponentName) [AvailableTarget (UnitId, ComponentName)] Source #
Given the install plan, produce the set of AvailableTarget
s for each
package-component pair.
Typically there will only be one such target for each component, but for example if we have a plan with both normal and profiling variants of a component then we would get both as available targets, or similarly if we had a plan that contained two instances of the same version of a package. This approach makes it relatively easy to select all instances/variants of a component.
data AvailableTarget k Source #
An available target represents a component within a package that a user command could plausibly refer to. In this sense, all the components defined within the package are things the user could refer to, whether or not it would actually be possible to build that component.
In particular the available target contains an AvailableTargetStatus
which
informs us about whether it's actually possible to select this component to
be built, and if not why not. This detail makes it possible for command
implementations (like build
, test
etc) to accurately report why a target
cannot be used.
Note that the type parameter is used to help enforce that command
implementations can only select targets that can actually be built (by
forcing them to return the k
value for the selected targets).
In particular resolveTargets
makes use of this (with k
as
(
) to identify the targets thus selected.UnitId
, ComponentName')
Instances
Functor AvailableTarget Source # | |
Defined in Distribution.Client.ProjectPlanning fmap :: (a -> b) -> AvailableTarget a -> AvailableTarget b # (<$) :: a -> AvailableTarget b -> AvailableTarget a # | |
Show k => Show (AvailableTarget k) Source # | |
Defined in Distribution.Client.ProjectPlanning showsPrec :: Int -> AvailableTarget k -> ShowS # show :: AvailableTarget k -> String # showList :: [AvailableTarget k] -> ShowS # | |
Eq k => Eq (AvailableTarget k) Source # | |
Defined in Distribution.Client.ProjectPlanning (==) :: AvailableTarget k -> AvailableTarget k -> Bool # (/=) :: AvailableTarget k -> AvailableTarget k -> Bool # |
data AvailableTargetStatus k Source #
The status of a an AvailableTarget
component. This tells us whether
it's actually possible to select this component to be built, and if not
why not.
TargetDisabledByUser | When the user does |
TargetDisabledBySolver | When the solver could not enable tests |
TargetNotBuildable | When the component has |
TargetNotLocal | When the component is non-core in a non-local package |
TargetBuildable k TargetRequested | The target can or should be built |
Instances
data TargetRequested Source #
This tells us whether a target ought to be built by default, or only if
specifically requested. The policy is that components like libraries and
executables are built by default by build
, but test suites and benchmarks
are not, unless this is overridden in the project configuration.
TargetRequestedByDefault | To be built by default |
TargetNotRequestedByDefault | Not to be built by default |
Instances
Show TargetRequested Source # | |
Defined in Distribution.Client.ProjectPlanning showsPrec :: Int -> TargetRequested -> ShowS # show :: TargetRequested -> String # showList :: [TargetRequested] -> ShowS # | |
Eq TargetRequested Source # | |
Defined in Distribution.Client.ProjectPlanning (==) :: TargetRequested -> TargetRequested -> Bool # (/=) :: TargetRequested -> TargetRequested -> Bool # | |
Ord TargetRequested Source # | |
Defined in Distribution.Client.ProjectPlanning compare :: TargetRequested -> TargetRequested -> Ordering # (<) :: TargetRequested -> TargetRequested -> Bool # (<=) :: TargetRequested -> TargetRequested -> Bool # (>) :: TargetRequested -> TargetRequested -> Bool # (>=) :: TargetRequested -> TargetRequested -> Bool # max :: TargetRequested -> TargetRequested -> TargetRequested # min :: TargetRequested -> TargetRequested -> TargetRequested # |
data ComponentTarget Source #
Specific targets within a package or component to act on e.g. to build, haddock or open a repl.
Instances
data SubComponentTarget Source #
Either the component as a whole or detail about a file or module target within a component.
WholeComponent | The component as a whole |
ModuleTarget ModuleName | A specific module within a component. |
FileTarget FilePath | A specific file within a component. Note that this does not carry the file extension. |
Instances
showComponentTarget :: PackageId -> ComponentTarget -> String Source #
Unambiguously render a ComponentTarget
, e.g., to pass
to a Cabal Setup script.
nubComponentTargets :: [(ComponentTarget, a)] -> [(ComponentTarget, NonEmpty a)] Source #
Merge component targets that overlap each other. Specially when we have multiple targets for the same component and one of them refers to the whole component (rather than a module or file within) then all the other targets for that component are subsumed.
We also allow for information associated with each component target, and whenever we targets subsume each other we aggregate their associated info.
Selecting a plan subset
pruneInstallPlanToTargets :: TargetAction -> Map UnitId [ComponentTarget] -> ElaboratedInstallPlan -> ElaboratedInstallPlan Source #
Given a set of per-package/per-component targets, take the subset of the install plan needed to build those targets. Also, update the package config to specify which optional stanzas to enable, and which targets within each package to build.
NB: Pruning happens after improvement, which is important because we will prune differently depending on what is already installed (to implement "sticky" test suite enabling behavior).
data TargetAction Source #
How pruneInstallPlanToTargets
should interpret the per-package
ComponentTarget
s: as build, repl or haddock targets.
pruneInstallPlanToDependencies :: Set UnitId -> ElaboratedInstallPlan -> Either CannotPruneDependencies ElaboratedInstallPlan Source #
Try to remove the given targets from the install plan.
This is not always possible.
newtype CannotPruneDependencies Source #
It is not always possible to prune to only the dependencies of a set of targets. It may be the case that removing a package leaves something else that still needed the pruned package.
This lists all the packages that would be broken, and their dependencies that would be missing if we did prune.
Instances
Show CannotPruneDependencies Source # | |
Defined in Distribution.Client.ProjectPlanning showsPrec :: Int -> CannotPruneDependencies -> ShowS # show :: CannotPruneDependencies -> String # showList :: [CannotPruneDependencies] -> ShowS # |
Utils required for building
elabBuildTargetWholeComponents :: ElaboratedConfiguredPackage -> Set ComponentName Source #
The components that we'll build all of, meaning that after they're built we can skip building them again (unlike with building just some modules or other files within a component).
configureCompiler :: Verbosity -> DistDirLayout -> ProjectConfig -> Rebuild (Compiler, Platform, ProgramDb) Source #
Setup.hs CLI flags for building
setupHsScriptOptions :: ElaboratedReadyPackage -> ElaboratedInstallPlan -> ElaboratedSharedConfig -> DistDirLayout -> SymbolicPath CWD (Dir Pkg) -> SymbolicPath Pkg (Dir Dist) -> Bool -> Lock -> SetupScriptOptions Source #
setupHsCommonFlags :: Verbosity -> Maybe (SymbolicPath CWD (Dir Pkg)) -> SymbolicPath Pkg (Dir Dist) -> CommonSetupFlags Source #
setupHsConfigureFlags Source #
:: Monad m | |
=> (FilePath -> m (SymbolicPath Pkg (Dir PkgDB))) | How to transform a path which is relative to cabal-install cwd to one which is relative to the route of the package about to be compiled. The simplest way to do this is to convert the potentially relative path into an absolute path. |
-> ElaboratedInstallPlan | |
-> ElaboratedReadyPackage | |
-> ElaboratedSharedConfig | |
-> CommonSetupFlags | |
-> m ConfigFlags |
setupHsBuildFlags :: Flag String -> ElaboratedConfiguredPackage -> ElaboratedSharedConfig -> CommonSetupFlags -> BuildFlags Source #
setupHsReplFlags :: ElaboratedConfiguredPackage -> ElaboratedSharedConfig -> CommonSetupFlags -> ReplFlags Source #
setupHsBenchFlags :: ElaboratedConfiguredPackage -> ElaboratedSharedConfig -> CommonSetupFlags -> BenchmarkFlags Source #
setupHsCopyFlags :: ElaboratedConfiguredPackage -> ElaboratedSharedConfig -> CommonSetupFlags -> FilePath -> CopyFlags Source #
setupHsRegisterFlags :: ElaboratedConfiguredPackage -> ElaboratedSharedConfig -> CommonSetupFlags -> FilePath -> RegisterFlags Source #
setupHsHaddockFlags :: ElaboratedConfiguredPackage -> ElaboratedSharedConfig -> BuildTimeSettings -> CommonSetupFlags -> HaddockFlags Source #
packageHashInputs :: ElaboratedSharedConfig -> ElaboratedConfiguredPackage -> PackageHashInputs Source #
Path construction
binDirectoryFor :: DistDirLayout -> ElaboratedSharedConfig -> ElaboratedConfiguredPackage -> FilePath -> FilePath Source #
The path to the directory that contains a specific executable. NB: For inplace NOT InstallPaths.bindir installDirs; for an inplace build those values are utter nonsense. So we have to guess where the directory is going to be. Fortunately this is "stable" part of Cabal API. But the way we get the build directory is A HORRIBLE HACK.
binDirectories :: DistDirLayout -> ElaboratedSharedConfig -> ElaboratedConfiguredPackage -> [FilePath] Source #
Get the bin/ directories that a package's executables should reside in.
The result may be empty if the package does not build any executables.
The result may have several entries if this is an inplace build of a package with multiple executables.