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

Distribution.Client.ProjectOrchestration

Description

This module deals with building and incrementally rebuilding a collection of packages. It is what backs the cabal build and configure commands, as well as being a core part of run, test, bench and others.

The primary thing is in fact rebuilding (and trying to make that quick by not redoing unnecessary work), so building from scratch is just a special case.

The build process and the code can be understood by breaking it down into three major parts:

As far as possible, the "what to do" phase embodies all the policy, leaving the "do it" phase policy free. The first phase contains more of the complicated logic, but it is contained in code that is either pure or just has read effects (except cache updates). Then the second phase does all the actions to build packages, but as far as possible it just follows the instructions and avoids any logic for deciding what to do (apart from recompilation avoidance in executing the plan).

This division helps us keep the code under control, making it easier to understand, test and debug. So when you are extending these modules, please think about which parts of your change belong in which part. It is perfectly ok to extend the description of what to do (i.e. the ElaboratedInstallPlan) if that helps keep the policy decisions in the first phase. Also, the second phase does not have direct access to any of the input configuration anyway; all the information has to flow via the ElaboratedInstallPlan.

Synopsis

Discovery phase: what is in the project?

data CurrentCommand Source #

Tracks what command is being executed, because we need to hide this somewhere for cases that need special handling (usually for error reporting).

data ProjectBaseContext Source #

This holds the context of a project prior to solving: the content of the cabal.project and all the local package .cabal files.

data BuildTimeSettings Source #

Resolved configuration for things that affect how we build and not the value of the things we build. The idea is that this is easier to use than the raw configuration because in the raw configuration everything is optional (monoidial). In the BuildTimeSettings every field is filled in, if only with the defaults.

Use resolveBuildTimeSettings to make one from the project config (by applying defaults etc).

commandLineFlagsToProjectConfig :: GlobalFlags -> NixStyleFlags a -> ClientInstallFlags -> ProjectConfig Source #

Convert configuration from the cabal configure or cabal build command line into a ProjectConfig value that can combined with configuration from other sources.

At the moment this uses the legacy command line flag types. See LegacyProjectConfig for an explanation.

Pre-build phase: decide what to do.

withInstallPlan :: Verbosity -> ProjectBaseContext -> (ElaboratedInstallPlan -> ElaboratedSharedConfig -> IO a) -> IO a Source #

Pre-build phase: decide what to do.

data ProjectBuildContext Source #

This holds the context between the pre-build, build and post-build phases.

Constructors

ProjectBuildContext 

Fields

Selecting what targets we mean

readTargetSelectors Source #

Arguments

:: [PackageSpecifier (SourcePackage (PackageLocation a))] 
-> Maybe ComponentKindFilter

This parameter is used when there are ambiguous selectors. If it is Just, then we attempt to resolve ambiguity by applying it, since otherwise there is no way to allow contextually valid yet syntactically ambiguous selectors. (5461)

-> [String] 
-> IO (Either [TargetSelectorProblem] [TargetSelector]) 

Parse a bunch of command line args as TargetSelectors, failing with an error if any are unrecognised. The possible target selectors are based on the available packages (and their locations).

reportTargetSelectorProblems :: Verbosity -> [TargetSelectorProblem] -> IO a Source #

Throw an exception with a formatted message if there are any problems.

resolveTargets :: forall err. (forall k. TargetSelector -> [AvailableTarget k] -> Either (TargetProblem err) [k]) -> (forall k. SubComponentTarget -> AvailableTarget k -> Either (TargetProblem err) k) -> ElaboratedInstallPlan -> Maybe SourcePackageDb -> [TargetSelector] -> Either [TargetProblem err] TargetsMap Source #

Given a set of TargetSelectors, resolve which UnitIds and ComponentTargets they ought to refer to.

The idea is that every user target identifies one or more roots in the ElaboratedInstallPlan, which we will use to determine the closure of what packages need to be built, dropping everything from the plan that is unnecessary. This closure and pruning is done by pruneInstallPlanToTargets and this needs to be told the roots in terms of UnitIds and the ComponentTargets within those.

This means we first need to translate the TargetSelectors into the UnitIds and ComponentTargets. This translation has to be different for the different command line commands, like build, repl etc. For example the command build pkgfoo could select a different set of components in pkgfoo than repl pkgfoo. The build command would select any library and all executables, whereas repl would select the library or a single executable. Furthermore, both of these examples could fail, and fail in different ways and each needs to be able to produce helpful error messages.

So resolveTargets takes two helpers: one to select the targets to be used by user targets that refer to a whole package (TargetPackage), and another to check user targets that refer to a component (or a module or file within a component). These helpers can fail, and use their own error type. Both helpers get given the AvailableTarget info about the component(s).

While commands vary quite a bit in their behaviour about which components to select for a whole-package target, most commands have the same behaviour for checking a user target that refers to a specific component. To help with this commands can use selectComponentTargetBasic, either directly or as a basis for their own selectComponentTarget implementation.

type TargetsMap = Map UnitId [(ComponentTarget, NonEmpty TargetSelector)] Source #

The set of components to build, represented as a mapping from UnitIds to the ComponentTargets within the unit that will be selected (e.g. selected to build, test or repl).

Associated with each ComponentTarget is the set of TargetSelectors that matched this target. Typically this is exactly one, but in general it is possible to for different selectors to match the same target. This extra information is primarily to help make helpful error messages.

allTargetSelectors :: TargetsMap -> [TargetSelector] Source #

Get all target selectors.

uniqueTargetSelectors :: TargetsMap -> [TargetSelector] Source #

Get all unique target selectors.

data TargetSelector Source #

A target selector is expression selecting a set of components (as targets for a actions like build, run, test etc). A target selector corresponds to the user syntax for referring to targets on the command line.

From the users point of view a target can be many things: packages, dirs, component names, files etc. Internally we consider a target to be a specific component (or module/file within a component), and all the users' notions of targets are just different ways of referring to these component targets.

So target selectors are expressions in the sense that they are interpreted to refer to one or more components. For example a TargetPackage gets interpreted differently by different commands to refer to all or a subset of components within the package.

The syntax has lots of optional parts:

[ package name | package dir | package .cabal file ]
[ [lib:|exe:] component name ]
[ module name | source file ]

Constructors

TargetPackage TargetImplicitCwd [PackageId] (Maybe ComponentKindFilter)

One (or more) packages as a whole, or all the components of a particular kind within the package(s).

These are always packages that are local to the project. In the case that there is more than one, they all share the same directory location.

TargetPackageNamed PackageName (Maybe ComponentKindFilter)

A package specified by name. This may refer to extra-packages from the cabal.project file, or a dependency of a known project package or could refer to a package from a hackage archive. It needs further context to resolve to a specific package.

TargetAllPackages (Maybe ComponentKindFilter)

All packages, or all components of a particular kind in all packages.

TargetComponent PackageId ComponentName SubComponentTarget

A specific component in a package within the project.

TargetComponentUnknown PackageName (Either UnqualComponentName ComponentName) SubComponentTarget

A component in a package, but where it cannot be verified that the package has such a component, or because the package is itself not known.

Instances

Instances details
Eq TargetSelector Source # 
Instance details

Defined in Distribution.Client.TargetSelector

Ord TargetSelector Source # 
Instance details

Defined in Distribution.Client.TargetSelector

Show TargetSelector Source # 
Instance details

Defined in Distribution.Client.TargetSelector

Generic TargetSelector Source # 
Instance details

Defined in Distribution.Client.TargetSelector

Associated Types

type Rep TargetSelector :: Type -> Type #

type Rep TargetSelector Source # 
Instance details

Defined in Distribution.Client.TargetSelector

type Rep TargetSelector = D1 ('MetaData "TargetSelector" "Distribution.Client.TargetSelector" "cabal-install-3.8.1.0-7iNu5HGLMqL9QLfLAUJqbd" 'False) ((C1 ('MetaCons "TargetPackage" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TargetImplicitCwd) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [PackageId]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ComponentKindFilter)))) :+: C1 ('MetaCons "TargetPackageNamed" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PackageName) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ComponentKindFilter)))) :+: (C1 ('MetaCons "TargetAllPackages" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ComponentKindFilter))) :+: (C1 ('MetaCons "TargetComponent" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PackageId) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ComponentName) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SubComponentTarget))) :+: C1 ('MetaCons "TargetComponentUnknown" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PackageName) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Either UnqualComponentName ComponentName)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SubComponentTarget))))))

data TargetImplicitCwd Source #

Does this TargetPackage selector arise from syntax referring to a package in the current directory (e.g. tests or no giving no explicit target at all) or does it come from syntax referring to a package name or location.

Instances

Instances details
Eq TargetImplicitCwd Source # 
Instance details

Defined in Distribution.Client.TargetSelector

Ord TargetImplicitCwd Source # 
Instance details

Defined in Distribution.Client.TargetSelector

Show TargetImplicitCwd Source # 
Instance details

Defined in Distribution.Client.TargetSelector

Generic TargetImplicitCwd Source # 
Instance details

Defined in Distribution.Client.TargetSelector

Associated Types

type Rep TargetImplicitCwd :: Type -> Type #

type Rep TargetImplicitCwd Source # 
Instance details

Defined in Distribution.Client.TargetSelector

type Rep TargetImplicitCwd = D1 ('MetaData "TargetImplicitCwd" "Distribution.Client.TargetSelector" "cabal-install-3.8.1.0-7iNu5HGLMqL9QLfLAUJqbd" 'False) (C1 ('MetaCons "TargetImplicitCwd" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TargetExplicitNamed" 'PrefixI 'False) (U1 :: Type -> Type))

type PackageId = PackageIdentifier #

Type alias so we can use the shorter name PackageId.

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 ComponentName #

Instances

Instances details
Eq ComponentName 
Instance details

Defined in Distribution.Types.ComponentName

Ord ComponentName 
Instance details

Defined in Distribution.Types.ComponentName

Read ComponentName 
Instance details

Defined in Distribution.Types.ComponentName

Show ComponentName 
Instance details

Defined in Distribution.Types.ComponentName

Generic ComponentName 
Instance details

Defined in Distribution.Types.ComponentName

Associated Types

type Rep ComponentName :: Type -> Type #

Binary ComponentName 
Instance details

Defined in Distribution.Types.ComponentName

Structured ComponentName 
Instance details

Defined in Distribution.Types.ComponentName

Parsec ComponentName 
Instance details

Defined in Distribution.Types.ComponentName

Pretty ComponentName 
Instance details

Defined in Distribution.Types.ComponentName

type Rep ComponentName 
Instance details

Defined in Distribution.Types.ComponentName

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

selectComponentTargetBasic :: SubComponentTarget -> AvailableTarget k -> Either (TargetProblem a) k Source #

A basic selectComponentTarget implementation to use or pass to resolveTargets, that does the basic checks that the component is buildable and isn't a test suite or benchmark that is disabled. This can also be used to do these basic checks as part of a custom impl that

distinctTargetComponents :: TargetsMap -> Set (UnitId, ComponentName) Source #

Utility used by repl and run to check if the targets spans multiple components, since those commands do not support multiple components.

Utils for selecting targets

Adjusting the plan

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.

printPlan :: Verbosity -> ProjectBaseContext -> ProjectBuildContext -> IO () Source #

Print a user-oriented presentation of the install plan, indicating what will be built.

Build phase: now do it.

runProjectBuildPhase :: Verbosity -> ProjectBaseContext -> ProjectBuildContext -> IO BuildOutcomes Source #

Build phase: now do it.

Execute all or parts of the description of what to do to build or rebuild the various packages needed.

Post build actions

runProjectPostBuildPhase :: Verbosity -> ProjectBaseContext -> ProjectBuildContext -> BuildOutcomes -> IO () Source #

Post-build phase: various administrative tasks

Update bits of state based on the build outcomes and report any failures.

dieOnBuildFailures :: Verbosity -> CurrentCommand -> ElaboratedInstallPlan -> BuildOutcomes -> IO () Source #

If there are build failures then report them and throw an exception.

Dummy projects

establishDummyProjectBaseContext Source #

Arguments

:: Verbosity 
-> ProjectConfig

Project configuration including the global config if needed

-> DistDirLayout

Where to put the dist directory

-> [PackageSpecifier UnresolvedSourcePackage]

The packages to be included in the project

-> CurrentCommand 
-> IO ProjectBaseContext 

Create a dummy project context, without a .cabal or a .cabal.project file (a place where to put a temporary dist directory is still needed)