cabal-install-3.10.1.0: The command-line interface for Cabal and Hackage.
Copyright(c) David Himmelstrup 2005
Bjorn Bringert 2007
Duncan Coutts 2008
LicenseBSD-like
Maintainercabal-devel@gmail.com
Stabilityprovisional
Portabilityportable
Safe HaskellSafe-Inferred
LanguageHaskell2010

Distribution.Client.Dependency

Description

Top level interface to dependency resolution.

Synopsis

The main package dependency resolver

data DepResolverParams Source #

The set of parameters to the dependency resolver. These parameters are relatively low level but many kinds of high level policies can be implemented in terms of adjustments to the parameters.

resolveDependencies :: Platform -> CompilerInfo -> PkgConfigDb -> Solver -> DepResolverParams -> Progress String String SolverInstallPlan Source #

Run the dependency solver.

Since this is potentially an expensive operation, the result is wrapped in a a Progress structure that can be unfolded to provide progress information, logging messages and the final result or an error.

data Progress step fail done #

A type to represent the unfolding of an expensive long running calculation that may fail. We may get intermediate steps before the final result which may be used to indicate progress and/or logging messages.

Constructors

Step step (Progress step fail done) 
Fail fail 
Done done 

Instances

Instances details
Monoid fail => Alternative (Progress step fail) 
Instance details

Defined in Distribution.Solver.Types.Progress

Methods

empty :: Progress step fail a #

(<|>) :: Progress step fail a -> Progress step fail a -> Progress step fail a #

some :: Progress step fail a -> Progress step fail [a] #

many :: Progress step fail a -> Progress step fail [a] #

Applicative (Progress step fail) 
Instance details

Defined in Distribution.Solver.Types.Progress

Methods

pure :: a -> Progress step fail a #

(<*>) :: Progress step fail (a -> b) -> Progress step fail a -> Progress step fail b #

liftA2 :: (a -> b -> c) -> Progress step fail a -> Progress step fail b -> Progress step fail c #

(*>) :: Progress step fail a -> Progress step fail b -> Progress step fail b #

(<*) :: Progress step fail a -> Progress step fail b -> Progress step fail a #

Functor (Progress step fail) 
Instance details

Defined in Distribution.Solver.Types.Progress

Methods

fmap :: (a -> b) -> Progress step fail a -> Progress step fail b #

(<$) :: a -> Progress step fail b -> Progress step fail a #

Monad (Progress step fail) 
Instance details

Defined in Distribution.Solver.Types.Progress

Methods

(>>=) :: Progress step fail a -> (a -> Progress step fail b) -> Progress step fail b #

(>>) :: Progress step fail a -> Progress step fail b -> Progress step fail b #

return :: a -> Progress step fail a #

foldProgress :: (step -> a -> a) -> (fail -> a) -> (done -> a) -> Progress step fail done -> a #

Consume a Progress calculation. Much like foldr for lists but with two base cases, one for a final result and one for failure.

Eg to convert into a simple Either result use:

foldProgress (flip const) Left Right

Alternate, simple resolver that does not do dependencies recursively

resolveWithoutDependencies :: DepResolverParams -> Either [ResolveNoDepsError] [UnresolvedSourcePackage] Source #

A simplistic method of resolving a list of target package names to available packages.

Specifically, it does not consider package dependencies at all. Unlike resolveDependencies, no attempt is made to ensure that the selected packages have dependencies that are satisfiable or consistent with each other.

It is suitable for tasks such as selecting packages to download for user inspection. It is not suitable for selecting packages to install.

Note: if no installed package index is available, it is OK to pass mempty. It simply means preferences for installed packages will be ignored.

Constructing resolver policies

data PackageProperty #

A package property is a logical predicate on packages.

Instances

Instances details
Structured PackageProperty 
Instance details

Defined in Distribution.Solver.Types.PackageConstraint

Generic PackageProperty 
Instance details

Defined in Distribution.Solver.Types.PackageConstraint

Associated Types

type Rep PackageProperty :: Type -> Type #

Show PackageProperty 
Instance details

Defined in Distribution.Solver.Types.PackageConstraint

Binary PackageProperty 
Instance details

Defined in Distribution.Solver.Types.PackageConstraint

Eq PackageProperty 
Instance details

Defined in Distribution.Solver.Types.PackageConstraint

type Rep PackageProperty 
Instance details

Defined in Distribution.Solver.Types.PackageConstraint

type Rep PackageProperty = D1 ('MetaData "PackageProperty" "Distribution.Solver.Types.PackageConstraint" "cabal-install-solver-3.10.1.0-C5SFSwS2IIlEouIBri9YCY" 'False) ((C1 ('MetaCons "PackagePropertyVersion" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 VersionRange)) :+: C1 ('MetaCons "PackagePropertyInstalled" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "PackagePropertySource" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "PackagePropertyFlags" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FlagAssignment)) :+: C1 ('MetaCons "PackagePropertyStanzas" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [OptionalStanza])))))

data PackageConstraint #

A package constraint consists of a scope plus a property that must hold for all packages within that scope.

scopeToplevel :: PackageName -> ConstraintScope #

Constructor for a common use case: the constraint applies to the package with the specified name when that package is a top-level dependency in the default namespace.

data PackagesPreferenceDefault Source #

Global policy for all packages to say if we prefer package versions that are already installed locally or if we just prefer the latest available.

Constructors

PreferAllLatest

Always prefer the latest version irrespective of any existing installed version.

  • This is the standard policy for upgrade.
PreferAllOldest

Always prefer the oldest version irrespective of any existing installed version or packages explicitly requested.

  • This is enabled by --prefer-oldest.
PreferAllInstalled

Always prefer the installed versions over ones that would need to be installed. Secondarily, prefer latest versions (eg the latest installed version or if there are none then the latest source version).

PreferLatestForSelected

Prefer the latest version for packages that are explicitly requested but prefers the installed version for any other packages.

  • This is the standard policy for install.

data PackagePreference Source #

A package selection preference for a particular package.

Preferences are soft constraints that the dependency resolver should try to respect where possible. It is not specified if preferences on some packages are more important than others.

Constructors

PackageVersionPreference PackageName VersionRange

A suggested constraint on the version number.

PackageInstalledPreference PackageName InstalledPreference

If we prefer versions of packages that are already installed.

PackageStanzasPreference PackageName [OptionalStanza]

If we would prefer to enable these optional stanzas (i.e. test suites and/or benchmarks)

Standard policy

standardInstallPolicy :: InstalledPackageIndex -> SourcePackageDb -> [PackageSpecifier UnresolvedSourcePackage] -> DepResolverParams Source #

The policy used by all the standard commands, install, fetch, freeze etc (but not the v2-build and related commands).

It extends the basicInstallPolicy with a policy on setup deps.

data PackageSpecifier pkg Source #

A fully or partially resolved reference to a package.

Constructors

NamedPackage PackageName [PackageProperty]

A partially specified reference to a package (either source or installed). It is specified by package name and optionally some required properties. Use a dependency resolver to pick a specific package satisfying these properties.

SpecificSourcePackage pkg

A fully specified source package.

Instances

Instances details
Functor PackageSpecifier Source # 
Instance details

Defined in Distribution.Client.Types.PackageSpecifier

Methods

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

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

Structured pkg => Structured (PackageSpecifier pkg) Source # 
Instance details

Defined in Distribution.Client.Types.PackageSpecifier

Generic (PackageSpecifier pkg) Source # 
Instance details

Defined in Distribution.Client.Types.PackageSpecifier

Associated Types

type Rep (PackageSpecifier pkg) :: Type -> Type #

Show pkg => Show (PackageSpecifier pkg) Source # 
Instance details

Defined in Distribution.Client.Types.PackageSpecifier

Binary pkg => Binary (PackageSpecifier pkg) Source # 
Instance details

Defined in Distribution.Client.Types.PackageSpecifier

Eq pkg => Eq (PackageSpecifier pkg) Source # 
Instance details

Defined in Distribution.Client.Types.PackageSpecifier

type Rep (PackageSpecifier pkg) Source # 
Instance details

Defined in Distribution.Client.Types.PackageSpecifier

type Rep (PackageSpecifier pkg) = D1 ('MetaData "PackageSpecifier" "Distribution.Client.Types.PackageSpecifier" "cabal-install-3.10.1.0-FbhGUvZ0l0XIx7QbOQfSVh" 'False) (C1 ('MetaCons "NamedPackage" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PackageName) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [PackageProperty])) :+: C1 ('MetaCons "SpecificSourcePackage" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 pkg)))

Extra policy options

Policy utils

removeUpperBounds :: AllowNewer -> DepResolverParams -> DepResolverParams Source #

Remove upper bounds in dependencies using the policy specified by the AllowNewer argument (allsomenone).

Note: It's important to apply removeUpperBounds after addSourcePackages. Otherwise, the packages inserted by addSourcePackages won't have upper bounds in dependencies relaxed.

addDefaultSetupDependencies :: (UnresolvedSourcePackage -> Maybe [Dependency]) -> DepResolverParams -> DepResolverParams Source #

Supply defaults for packages without explicit Setup dependencies

Note: It's important to apply addDefaultSetupDepends after addSourcePackages. Otherwise, the packages inserted by addSourcePackages won't have upper bounds in dependencies relaxed.

addSetupCabalMinVersionConstraint :: Version -> DepResolverParams -> DepResolverParams Source #

If a package has a custom setup then we need to add a setup-depends on Cabal.