Copyright | (c) Duncan Coutts 2012 2015 2016 |
---|---|
License | BSD-like |
Maintainer | [email protected] |
Safe Haskell | None |
Language | Haskell2010 |
Distribution.Client.TargetSelector
Description
Handling for user-specified target selectors.
Synopsis
- data TargetSelector
- = TargetPackage TargetImplicitCwd [PackageId] (Maybe ComponentKindFilter)
- | TargetPackageNamed PackageName (Maybe ComponentKindFilter)
- | TargetAllPackages (Maybe ComponentKindFilter)
- | TargetComponent PackageId ComponentName SubComponentTarget
- | TargetComponentUnknown PackageName (Either UnqualComponentName ComponentName) SubComponentTarget
- data TargetImplicitCwd
- data ComponentKind
- type ComponentKindFilter = ComponentKind
- data SubComponentTarget
- data QualLevel
- componentKind :: ComponentName -> ComponentKind
- readTargetSelectors :: [PackageSpecifier (SourcePackage (PackageLocation a))] -> Maybe ComponentKindFilter -> [String] -> IO (Either [TargetSelectorProblem] [TargetSelector])
- data TargetSelectorProblem
- = TargetSelectorExpected TargetString [String] String
- | TargetSelectorNoSuch TargetString [(Maybe (String, String), String, String, [String])]
- | TargetSelectorAmbiguous TargetString [(TargetString, TargetSelector)]
- | MatchingInternalError TargetString TargetSelector [(TargetString, [TargetSelector])]
- | TargetSelectorUnrecognised String
- | TargetSelectorNoCurrentPackage TargetString
- | TargetSelectorNoTargetsInCwd Bool
- | TargetSelectorNoTargetsInProject
- | TargetSelectorNoScript TargetString
- reportTargetSelectorProblems :: Verbosity -> [TargetSelectorProblem] -> IO a
- showTargetSelector :: TargetSelector -> String
- data TargetString
- showTargetString :: TargetString -> String
- parseTargetString :: String -> Maybe TargetString
- readTargetSelectorsWith :: (Applicative m, Monad m) => DirActions m -> [PackageSpecifier (SourcePackage (PackageLocation a))] -> Maybe ComponentKindFilter -> [String] -> m (Either [TargetSelectorProblem] [TargetSelector])
- data DirActions (m :: Type -> Type) = DirActions {
- doesFileExist :: FilePath -> m Bool
- doesDirectoryExist :: FilePath -> m Bool
- canonicalizePath :: FilePath -> m FilePath
- getCurrentDirectory :: m FilePath
- defaultDirActions :: DirActions IO
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 |
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
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.
Constructors
TargetImplicitCwd | |
TargetExplicitNamed |
Instances
Generic TargetImplicitCwd Source # | |||||
Defined in Distribution.Client.TargetSelector Associated Types
Methods from :: TargetImplicitCwd -> Rep TargetImplicitCwd x # to :: Rep TargetImplicitCwd x -> TargetImplicitCwd # | |||||
Show TargetImplicitCwd Source # | |||||
Defined in Distribution.Client.TargetSelector Methods showsPrec :: Int -> TargetImplicitCwd -> ShowS # show :: TargetImplicitCwd -> String # showList :: [TargetImplicitCwd] -> ShowS # | |||||
Eq TargetImplicitCwd Source # | |||||
Defined in Distribution.Client.TargetSelector Methods (==) :: TargetImplicitCwd -> TargetImplicitCwd -> Bool # (/=) :: TargetImplicitCwd -> TargetImplicitCwd -> Bool # | |||||
Ord TargetImplicitCwd Source # | |||||
Defined in Distribution.Client.TargetSelector Methods compare :: TargetImplicitCwd -> TargetImplicitCwd -> Ordering # (<) :: TargetImplicitCwd -> TargetImplicitCwd -> Bool # (<=) :: TargetImplicitCwd -> TargetImplicitCwd -> Bool # (>) :: TargetImplicitCwd -> TargetImplicitCwd -> Bool # (>=) :: TargetImplicitCwd -> TargetImplicitCwd -> Bool # max :: TargetImplicitCwd -> TargetImplicitCwd -> TargetImplicitCwd # min :: TargetImplicitCwd -> TargetImplicitCwd -> TargetImplicitCwd # | |||||
type Rep TargetImplicitCwd Source # | |||||
Defined in Distribution.Client.TargetSelector type Rep TargetImplicitCwd = D1 ('MetaData "TargetImplicitCwd" "Distribution.Client.TargetSelector" "cabal-install-3.16.0.0-5Or0gjSnsvnBIy2HLcA6Z9" 'False) (C1 ('MetaCons "TargetImplicitCwd" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TargetExplicitNamed" 'PrefixI 'False) (U1 :: Type -> Type)) |
data ComponentKind Source #
Instances
Enum ComponentKind Source # | |
Defined in Distribution.Client.TargetSelector Methods succ :: ComponentKind -> ComponentKind # pred :: ComponentKind -> ComponentKind # toEnum :: Int -> ComponentKind # fromEnum :: ComponentKind -> Int # enumFrom :: ComponentKind -> [ComponentKind] # enumFromThen :: ComponentKind -> ComponentKind -> [ComponentKind] # enumFromTo :: ComponentKind -> ComponentKind -> [ComponentKind] # enumFromThenTo :: ComponentKind -> ComponentKind -> ComponentKind -> [ComponentKind] # | |
Show ComponentKind Source # | |
Defined in Distribution.Client.TargetSelector Methods showsPrec :: Int -> ComponentKind -> ShowS # show :: ComponentKind -> String # showList :: [ComponentKind] -> ShowS # | |
Eq ComponentKind Source # | |
Defined in Distribution.Client.TargetSelector Methods (==) :: ComponentKind -> ComponentKind -> Bool # (/=) :: ComponentKind -> ComponentKind -> Bool # | |
Ord ComponentKind Source # | |
Defined in Distribution.Client.TargetSelector Methods compare :: ComponentKind -> ComponentKind -> Ordering # (<) :: ComponentKind -> ComponentKind -> Bool # (<=) :: ComponentKind -> ComponentKind -> Bool # (>) :: ComponentKind -> ComponentKind -> Bool # (>=) :: ComponentKind -> ComponentKind -> Bool # max :: ComponentKind -> ComponentKind -> ComponentKind # min :: ComponentKind -> ComponentKind -> ComponentKind # |
type ComponentKindFilter = ComponentKind Source #
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
Structured SubComponentTarget Source # | |||||
Defined in Distribution.Client.TargetSelector Methods structure :: Proxy SubComponentTarget -> Structure # structureHash' :: Tagged SubComponentTarget MD5 | |||||
Generic SubComponentTarget Source # | |||||
Defined in Distribution.Client.TargetSelector Associated Types
Methods from :: SubComponentTarget -> Rep SubComponentTarget x # to :: Rep SubComponentTarget x -> SubComponentTarget # | |||||
Show SubComponentTarget Source # | |||||
Defined in Distribution.Client.TargetSelector Methods showsPrec :: Int -> SubComponentTarget -> ShowS # show :: SubComponentTarget -> String # showList :: [SubComponentTarget] -> ShowS # | |||||
Binary SubComponentTarget Source # | |||||
Defined in Distribution.Client.TargetSelector Methods put :: SubComponentTarget -> Put # get :: Get SubComponentTarget # putList :: [SubComponentTarget] -> Put # | |||||
Eq SubComponentTarget Source # | |||||
Defined in Distribution.Client.TargetSelector Methods (==) :: SubComponentTarget -> SubComponentTarget -> Bool # (/=) :: SubComponentTarget -> SubComponentTarget -> Bool # | |||||
Ord SubComponentTarget Source # | |||||
Defined in Distribution.Client.TargetSelector Methods compare :: SubComponentTarget -> SubComponentTarget -> Ordering # (<) :: SubComponentTarget -> SubComponentTarget -> Bool # (<=) :: SubComponentTarget -> SubComponentTarget -> Bool # (>) :: SubComponentTarget -> SubComponentTarget -> Bool # (>=) :: SubComponentTarget -> SubComponentTarget -> Bool # max :: SubComponentTarget -> SubComponentTarget -> SubComponentTarget # min :: SubComponentTarget -> SubComponentTarget -> SubComponentTarget # | |||||
type Rep SubComponentTarget Source # | |||||
Defined in Distribution.Client.TargetSelector type Rep SubComponentTarget = D1 ('MetaData "SubComponentTarget" "Distribution.Client.TargetSelector" "cabal-install-3.16.0.0-5Or0gjSnsvnBIy2HLcA6Z9" '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)))) |
Qualification levels. Given the filepath src/F, executable component A, and package foo:
Instances
Enum QualLevel Source # | |
Defined in Distribution.Client.TargetSelector Methods succ :: QualLevel -> QualLevel # pred :: QualLevel -> QualLevel # fromEnum :: QualLevel -> Int # enumFrom :: QualLevel -> [QualLevel] # enumFromThen :: QualLevel -> QualLevel -> [QualLevel] # enumFromTo :: QualLevel -> QualLevel -> [QualLevel] # enumFromThenTo :: QualLevel -> QualLevel -> QualLevel -> [QualLevel] # | |
Show QualLevel Source # | |
Eq QualLevel Source # | |
Reading target selectors
Arguments
:: [PackageSpecifier (SourcePackage (PackageLocation a))] | |
-> Maybe ComponentKindFilter | This parameter is used when there are ambiguous selectors.
If it is |
-> [String] | |
-> IO (Either [TargetSelectorProblem] [TargetSelector]) |
Parse a bunch of command line args as TargetSelector
s, failing with an
error if any are unrecognised. The possible target selectors are based on
the available packages (and their locations).
data TargetSelectorProblem Source #
The various ways that trying to resolve a TargetString
to a
TargetSelector
can fail.
Constructors
TargetSelectorExpected TargetString [String] String |
|
TargetSelectorNoSuch TargetString [(Maybe (String, String), String, String, [String])] |
|
TargetSelectorAmbiguous TargetString [(TargetString, TargetSelector)] | |
MatchingInternalError TargetString TargetSelector [(TargetString, [TargetSelector])] | |
TargetSelectorUnrecognised String | Syntax error when trying to parse a target string. |
TargetSelectorNoCurrentPackage TargetString | |
TargetSelectorNoTargetsInCwd Bool | bool that flags when it is acceptable to suggest "all" as a target |
TargetSelectorNoTargetsInProject | |
TargetSelectorNoScript TargetString |
Instances
Show TargetSelectorProblem Source # | |
Defined in Distribution.Client.TargetSelector Methods showsPrec :: Int -> TargetSelectorProblem -> ShowS # show :: TargetSelectorProblem -> String # showList :: [TargetSelectorProblem] -> ShowS # | |
Eq TargetSelectorProblem Source # | |
Defined in Distribution.Client.TargetSelector Methods (==) :: TargetSelectorProblem -> TargetSelectorProblem -> Bool # (/=) :: TargetSelectorProblem -> TargetSelectorProblem -> Bool # |
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
Constructors
TargetString1 String | |
TargetString2 String String | |
TargetString3 String String String | |
TargetString4 String String String String | |
TargetString5 String String String String String | |
TargetString7 String String String String String String String |
Instances
Show TargetString Source # | |
Defined in Distribution.Client.TargetSelector Methods showsPrec :: Int -> TargetString -> ShowS # show :: TargetString -> String # showList :: [TargetString] -> ShowS # | |
Eq TargetString Source # | |
Defined in Distribution.Client.TargetSelector |
showTargetString :: TargetString -> String Source #
Render a TargetString
back as the external syntax. This is mainly for
error messages.
non-IO
readTargetSelectorsWith :: (Applicative m, Monad m) => DirActions m -> [PackageSpecifier (SourcePackage (PackageLocation a))] -> Maybe ComponentKindFilter -> [String] -> m (Either [TargetSelectorProblem] [TargetSelector]) Source #
data DirActions (m :: Type -> Type) Source #
Constructors
DirActions | |
Fields
|