cabal-install-3.8.1.0: The command-line interface for Cabal and Hackage.
Safe HaskellNone
LanguageHaskell2010

Distribution.Client.ProjectPlanning

Description

Planning how to build everything in a project.

Synopsis

elaborated install plan types

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 #

Constructors

ElaboratedConfiguredPackage 

Fields

Instances

Instances details
Eq ElaboratedConfiguredPackage Source # 
Instance details

Defined in Distribution.Client.ProjectPlanning.Types

Show ElaboratedConfiguredPackage Source # 
Instance details

Defined in Distribution.Client.ProjectPlanning.Types

Generic ElaboratedConfiguredPackage Source # 
Instance details

Defined in Distribution.Client.ProjectPlanning.Types

Associated Types

type Rep ElaboratedConfiguredPackage :: Type -> Type #

HasUnitId ElaboratedConfiguredPackage Source # 
Instance details

Defined in Distribution.Client.ProjectPlanning.Types

Package ElaboratedConfiguredPackage Source # 
Instance details

Defined in Distribution.Client.ProjectPlanning.Types

Binary ElaboratedConfiguredPackage Source # 
Instance details

Defined in Distribution.Client.ProjectPlanning.Types

Structured ElaboratedConfiguredPackage Source # 
Instance details

Defined in Distribution.Client.ProjectPlanning.Types

IsNode ElaboratedConfiguredPackage Source # 
Instance details

Defined in Distribution.Client.ProjectPlanning.Types

Associated Types

type Key ElaboratedConfiguredPackage #

HasConfiguredId ElaboratedConfiguredPackage Source # 
Instance details

Defined in Distribution.Client.ProjectPlanning.Types

type Rep ElaboratedConfiguredPackage Source # 
Instance details

Defined in Distribution.Client.ProjectPlanning.Types

type Rep ElaboratedConfiguredPackage = D1 ('MetaData "ElaboratedConfiguredPackage" "Distribution.Client.ProjectPlanning.Types" "cabal-install-3.8.1.0-7iNu5HGLMqL9QLfLAUJqbd" 'False) (C1 ('MetaCons "ElaboratedConfiguredPackage" 'PrefixI 'True) ((((((S1 ('MetaSel ('Just "elabUnitId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UnitId) :*: S1 ('MetaSel ('Just "elabComponentId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ComponentId)) :*: (S1 ('MetaSel ('Just "elabInstantiatedWith") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map ModuleName Module)) :*: (S1 ('MetaSel ('Just "elabLinkedInstantiatedWith") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map ModuleName OpenModule)) :*: S1 ('MetaSel ('Just "elabIsCanonical") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)))) :*: ((S1 ('MetaSel ('Just "elabPkgSourceId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PackageId) :*: S1 ('MetaSel ('Just "elabModuleShape") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ModuleShape)) :*: (S1 ('MetaSel ('Just "elabFlagAssignment") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FlagAssignment) :*: (S1 ('MetaSel ('Just "elabFlagDefaults") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FlagAssignment) :*: S1 ('MetaSel ('Just "elabPkgDescription") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PackageDescription))))) :*: (((S1 ('MetaSel ('Just "elabPkgSourceLocation") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (PackageLocation (Maybe FilePath))) :*: S1 ('MetaSel ('Just "elabPkgSourceHash") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe PackageSourceHash))) :*: (S1 ('MetaSel ('Just "elabLocalToProject") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: (S1 ('MetaSel ('Just "elabBuildStyle") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BuildStyle) :*: S1 ('MetaSel ('Just "elabEnabledSpec") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ComponentRequestedSpec)))) :*: ((S1 ('MetaSel ('Just "elabStanzasAvailable") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 OptionalStanzaSet) :*: (S1 ('MetaSel ('Just "elabStanzasRequested") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (OptionalStanzaMap (Maybe Bool))) :*: S1 ('MetaSel ('Just "elabPackageDbs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Maybe PackageDB]))) :*: (S1 ('MetaSel ('Just "elabSetupPackageDBStack") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PackageDBStack) :*: (S1 ('MetaSel ('Just "elabBuildPackageDBStack") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PackageDBStack) :*: S1 ('MetaSel ('Just "elabRegisterPackageDBStack") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PackageDBStack)))))) :*: ((((S1 ('MetaSel ('Just "elabInplaceSetupPackageDBStack") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PackageDBStack) :*: S1 ('MetaSel ('Just "elabInplaceBuildPackageDBStack") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PackageDBStack)) :*: (S1 ('MetaSel ('Just "elabInplaceRegisterPackageDBStack") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PackageDBStack) :*: (S1 ('MetaSel ('Just "elabPkgDescriptionOverride") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe CabalFileText)) :*: S1 ('MetaSel ('Just "elabVanillaLib") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)))) :*: ((S1 ('MetaSel ('Just "elabSharedLib") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: (S1 ('MetaSel ('Just "elabStaticLib") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "elabDynExe") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool))) :*: (S1 ('MetaSel ('Just "elabFullyStaticExe") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: (S1 ('MetaSel ('Just "elabGHCiLib") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "elabProfLib") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool))))) :*: (((S1 ('MetaSel ('Just "elabProfExe") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "elabProfLibDetail") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ProfDetailLevel)) :*: (S1 ('MetaSel ('Just "elabProfExeDetail") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ProfDetailLevel) :*: (S1 ('MetaSel ('Just "elabCoverage") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "elabOptimization") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 OptimisationLevel)))) :*: ((S1 ('MetaSel ('Just "elabSplitObjs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: (S1 ('MetaSel ('Just "elabSplitSections") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "elabStripLibs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool))) :*: (S1 ('MetaSel ('Just "elabStripExes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: (S1 ('MetaSel ('Just "elabDebugInfo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DebugInfoLevel) :*: S1 ('MetaSel ('Just "elabDumpBuildInfo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DumpBuildInfo))))))) :*: (((((S1 ('MetaSel ('Just "elabProgramPaths") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map String FilePath)) :*: S1 ('MetaSel ('Just "elabProgramArgs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map String [String]))) :*: (S1 ('MetaSel ('Just "elabProgramPathExtra") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [FilePath]) :*: (S1 ('MetaSel ('Just "elabConfigureScriptArgs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String]) :*: S1 ('MetaSel ('Just "elabExtraLibDirs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [FilePath])))) :*: ((S1 ('MetaSel ('Just "elabExtraLibDirsStatic") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [FilePath]) :*: S1 ('MetaSel ('Just "elabExtraFrameworkDirs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [FilePath])) :*: (S1 ('MetaSel ('Just "elabExtraIncludeDirs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [FilePath]) :*: (S1 ('MetaSel ('Just "elabProgPrefix") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe PathTemplate)) :*: S1 ('MetaSel ('Just "elabProgSuffix") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe PathTemplate)))))) :*: (((S1 ('MetaSel ('Just "elabInstallDirs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (InstallDirs FilePath)) :*: S1 ('MetaSel ('Just "elabHaddockHoogle") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)) :*: (S1 ('MetaSel ('Just "elabHaddockHtml") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: (S1 ('MetaSel ('Just "elabHaddockHtmlLocation") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe String)) :*: S1 ('MetaSel ('Just "elabHaddockForeignLibs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)))) :*: ((S1 ('MetaSel ('Just "elabHaddockForHackage") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 HaddockTarget) :*: (S1 ('MetaSel ('Just "elabHaddockExecutables") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "elabHaddockTestSuites") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool))) :*: (S1 ('MetaSel ('Just "elabHaddockBenchmarks") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: (S1 ('MetaSel ('Just "elabHaddockInternal") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "elabHaddockCss") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FilePath))))))) :*: ((((S1 ('MetaSel ('Just "elabHaddockLinkedSource") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "elabHaddockQuickJump") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)) :*: (S1 ('MetaSel ('Just "elabHaddockHscolourCss") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FilePath)) :*: (S1 ('MetaSel ('Just "elabHaddockContents") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe PathTemplate)) :*: S1 ('MetaSel ('Just "elabTestMachineLog") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe PathTemplate))))) :*: ((S1 ('MetaSel ('Just "elabTestHumanLog") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe PathTemplate)) :*: (S1 ('MetaSel ('Just "elabTestShowDetails") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe TestShowDetails)) :*: S1 ('MetaSel ('Just "elabTestKeepTix") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool))) :*: (S1 ('MetaSel ('Just "elabTestWrapper") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FilePath)) :*: (S1 ('MetaSel ('Just "elabTestFailWhenNoTestSuites") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "elabTestTestOptions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [PathTemplate]))))) :*: (((S1 ('MetaSel ('Just "elabBenchmarkOptions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [PathTemplate]) :*: S1 ('MetaSel ('Just "elabSetupScriptStyle") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SetupScriptStyle)) :*: (S1 ('MetaSel ('Just "elabSetupScriptCliVersion") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Version) :*: (S1 ('MetaSel ('Just "elabConfigureTargets") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ComponentTarget]) :*: S1 ('MetaSel ('Just "elabBuildTargets") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ComponentTarget])))) :*: ((S1 ('MetaSel ('Just "elabTestTargets") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ComponentTarget]) :*: (S1 ('MetaSel ('Just "elabBenchTargets") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ComponentTarget]) :*: S1 ('MetaSel ('Just "elabReplTarget") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ComponentTarget)))) :*: (S1 ('MetaSel ('Just "elabHaddockTargets") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ComponentTarget]) :*: (S1 ('MetaSel ('Just "elabBuildHaddocks") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "elabPkgOrComp") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ElaboratedPackageOrComponent)))))))))
type Key ElaboratedConfiguredPackage Source # 
Instance details

Defined in Distribution.Client.ProjectPlanning.Types

data ElaboratedSharedConfig Source #

Constructors

ElaboratedSharedConfig 

Fields

Instances

Instances details
Show ElaboratedSharedConfig Source # 
Instance details

Defined in Distribution.Client.ProjectPlanning.Types

Generic ElaboratedSharedConfig Source # 
Instance details

Defined in Distribution.Client.ProjectPlanning.Types

Associated Types

type Rep ElaboratedSharedConfig :: Type -> Type #

Binary ElaboratedSharedConfig Source # 
Instance details

Defined in Distribution.Client.ProjectPlanning.Types

Structured ElaboratedSharedConfig Source # 
Instance details

Defined in Distribution.Client.ProjectPlanning.Types

type Rep ElaboratedSharedConfig Source # 
Instance details

Defined in Distribution.Client.ProjectPlanning.Types

type Rep ElaboratedSharedConfig = D1 ('MetaData "ElaboratedSharedConfig" "Distribution.Client.ProjectPlanning.Types" "cabal-install-3.8.1.0-7iNu5HGLMqL9QLfLAUJqbd" 'False) (C1 ('MetaCons "ElaboratedSharedConfig" 'PrefixI 'True) ((S1 ('MetaSel ('Just "pkgConfigPlatform") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Platform) :*: S1 ('MetaSel ('Just "pkgConfigCompiler") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Compiler)) :*: (S1 ('MetaSel ('Just "pkgConfigCompilerProgs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ProgramDb) :*: S1 ('MetaSel ('Just "pkgConfigReplOptions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ReplOptions))))

data BuildStyle Source #

This is used in the install plan to indicate how the package will be built.

Constructors

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

The package is built, but the files are not installed anywhere, rather the build dir is kept and the package is registered inplace.

Such packages can still subsequently be installed.

Typically BuildAndInstall packages will only depend on other BuildAndInstall style packages and not on BuildInplaceOnly ones.

Instances

Instances details
Eq BuildStyle Source # 
Instance details

Defined in Distribution.Client.ProjectPlanning.Types

Show BuildStyle Source # 
Instance details

Defined in Distribution.Client.ProjectPlanning.Types

Generic BuildStyle Source # 
Instance details

Defined in Distribution.Client.ProjectPlanning.Types

Associated Types

type Rep BuildStyle :: Type -> Type #

Semigroup BuildStyle Source # 
Instance details

Defined in Distribution.Client.ProjectPlanning.Types

Monoid BuildStyle Source # 
Instance details

Defined in Distribution.Client.ProjectPlanning.Types

Binary BuildStyle Source # 
Instance details

Defined in Distribution.Client.ProjectPlanning.Types

Structured BuildStyle Source # 
Instance details

Defined in Distribution.Client.ProjectPlanning.Types

type Rep BuildStyle Source # 
Instance details

Defined in Distribution.Client.ProjectPlanning.Types

type Rep BuildStyle = D1 ('MetaData "BuildStyle" "Distribution.Client.ProjectPlanning.Types" "cabal-install-3.8.1.0-7iNu5HGLMqL9QLfLAUJqbd" 'False) (C1 ('MetaCons "BuildAndInstall" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BuildInplaceOnly" 'PrefixI 'False) (U1 :: Type -> Type))

Producing the elaborated install plan

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.

rebuildInstallPlan Source #

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 AvailableTargets 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 (UnitId, ComponentName')) to identify the targets thus selected.

Instances

Instances details
Functor AvailableTarget Source # 
Instance details

Defined in Distribution.Client.ProjectPlanning

Methods

fmap :: (a -> b) -> AvailableTarget a -> AvailableTarget b #

(<$) :: a -> AvailableTarget b -> AvailableTarget a #

Eq k => Eq (AvailableTarget k) Source # 
Instance details

Defined in Distribution.Client.ProjectPlanning

Show k => Show (AvailableTarget k) Source # 
Instance details

Defined in Distribution.Client.ProjectPlanning

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.

Constructors

TargetDisabledByUser

When the user does tests: False

TargetDisabledBySolver

When the solver could not enable tests

TargetNotBuildable

When the component has buildable: False

TargetNotLocal

When the component is non-core in a non-local package

TargetBuildable k TargetRequested

The target can or should be built

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.

Constructors

TargetRequestedByDefault

To be built by default

TargetNotRequestedByDefault

Not to be built by default

data ComponentTarget Source #

Specific targets within a package or component to act on e.g. to build, haddock or open a repl.

Instances

Instances details
Eq ComponentTarget Source # 
Instance details

Defined in Distribution.Client.ProjectPlanning.Types

Ord ComponentTarget Source # 
Instance details

Defined in Distribution.Client.ProjectPlanning.Types

Show ComponentTarget Source # 
Instance details

Defined in Distribution.Client.ProjectPlanning.Types

Generic ComponentTarget Source # 
Instance details

Defined in Distribution.Client.ProjectPlanning.Types

Associated Types

type Rep ComponentTarget :: Type -> Type #

Binary ComponentTarget Source # 
Instance details

Defined in Distribution.Client.ProjectPlanning.Types

Structured ComponentTarget Source # 
Instance details

Defined in Distribution.Client.ProjectPlanning.Types

type Rep ComponentTarget Source # 
Instance details

Defined in Distribution.Client.ProjectPlanning.Types

type Rep ComponentTarget = D1 ('MetaData "ComponentTarget" "Distribution.Client.ProjectPlanning.Types" "cabal-install-3.8.1.0-7iNu5HGLMqL9QLfLAUJqbd" 'False) (C1 ('MetaCons "ComponentTarget" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ComponentName) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SubComponentTarget)))

data SubComponentTarget Source #

Either the component as a whole or detail about a file or module target within a component.

Constructors

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

Instances details
Eq SubComponentTarget Source # 
Instance details

Defined in Distribution.Client.TargetSelector

Ord SubComponentTarget Source # 
Instance details

Defined in Distribution.Client.TargetSelector

Show SubComponentTarget Source # 
Instance details

Defined in Distribution.Client.TargetSelector

Generic SubComponentTarget Source # 
Instance details

Defined in Distribution.Client.TargetSelector

Associated Types

type Rep SubComponentTarget :: Type -> Type #

Binary SubComponentTarget Source # 
Instance details

Defined in Distribution.Client.TargetSelector

Structured SubComponentTarget Source # 
Instance details

Defined in Distribution.Client.TargetSelector

type Rep SubComponentTarget Source # 
Instance details

Defined in Distribution.Client.TargetSelector

type Rep SubComponentTarget = D1 ('MetaData "SubComponentTarget" "Distribution.Client.TargetSelector" "cabal-install-3.8.1.0-7iNu5HGLMqL9QLfLAUJqbd" 'False) (C1 ('MetaCons "WholeComponent" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ModuleTarget" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ModuleName)) :+: C1 ('MetaCons "FileTarget" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FilePath))))

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).

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.

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).

Setup.hs CLI flags for building

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.