cabal-install-3.10.1.0: The command-line interface for Cabal and Hackage.
Copyright(c) Duncan Coutts 2012 2015 2016
LicenseBSD-like
Maintainerduncan@community.haskell.org
Safe HaskellSafe-Inferred
LanguageHaskell2010

Distribution.Client.TargetSelector

Description

Handling for user-specified target selectors.

Synopsis

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
Generic TargetSelector Source # 
Instance details

Defined in Distribution.Client.TargetSelector

Associated Types

type Rep TargetSelector :: Type -> Type #

Show TargetSelector Source # 
Instance details

Defined in Distribution.Client.TargetSelector

Eq TargetSelector Source # 
Instance details

Defined in Distribution.Client.TargetSelector

Ord TargetSelector Source # 
Instance details

Defined in Distribution.Client.TargetSelector

type Rep TargetSelector Source # 
Instance details

Defined in Distribution.Client.TargetSelector

type Rep TargetSelector = D1 ('MetaData "TargetSelector" "Distribution.Client.TargetSelector" "cabal-install-3.10.1.0-FbhGUvZ0l0XIx7QbOQfSVh" '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
Generic TargetImplicitCwd Source # 
Instance details

Defined in Distribution.Client.TargetSelector

Associated Types

type Rep TargetImplicitCwd :: Type -> Type #

Show TargetImplicitCwd Source # 
Instance details

Defined in Distribution.Client.TargetSelector

Eq TargetImplicitCwd Source # 
Instance details

Defined in Distribution.Client.TargetSelector

Ord TargetImplicitCwd Source # 
Instance details

Defined in Distribution.Client.TargetSelector

type Rep TargetImplicitCwd Source # 
Instance details

Defined in Distribution.Client.TargetSelector

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

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

Show SubComponentTarget Source # 
Instance details

Defined in Distribution.Client.TargetSelector

Binary SubComponentTarget Source # 
Instance details

Defined in Distribution.Client.TargetSelector

Eq SubComponentTarget Source # 
Instance details

Defined in Distribution.Client.TargetSelector

Ord 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.10.1.0-FbhGUvZ0l0XIx7QbOQfSVh" '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))))

data QualLevel Source #

Qualification levels. Given the filepath src/F, executable component A, and package foo:

Constructors

QL1
src/F
QL2
foo:srcF | A:srcF
QL3
foo:A:srcF | exe:A:srcF
QLFull
pkg:foo:exe:A:file:src/F

Reading target selectors

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. (#4676, #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.

data TargetString Source #

The outline parse of a target selector. It takes one of the forms:

str1
str1:str2
str1:str2:str3
str1:str2:str3:str4

showTargetString :: TargetString -> String Source #

Render a TargetString back as the external syntax. This is mainly for error messages.

non-IO