cabal-install-3.10.1.0: The command-line interface for Cabal and Hackage.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Distribution.Client.CmdErrorMessages

Description

Utilities to help format error messages for the various CLI commands.

Synopsis

Documentation

data Plural Source #

A tag used in rendering messages to distinguish singular or plural.

Constructors

Singular 
Plural 

plural :: Plural -> a -> a -> a Source #

Used to render a singular or plural version of something

plural (listPlural theThings) "it is" "they are"

listPlural :: [a] -> Plural Source #

Singular for singleton lists and plural otherwise.

renderListCommaAnd :: [String] -> String Source #

Render a list of things in the style foo, bar and baz

renderListSemiAnd :: [String] -> String Source #

Render a list of things in the style blah blah; this that; and the other

sortGroupOn :: Ord b => (a -> b) -> [a] -> [(b, [a])] Source #

When rendering lists of things it often reads better to group related things, e.g. grouping components by package name

renderListSemiAnd
  [     "the package " ++ prettyShow pkgname ++ " components "
     ++ renderListCommaAnd showComponentName components
  | (pkgname, components) <- sortGroupOn packageName allcomponents ]

optionalStanza :: ComponentName -> Maybe OptionalStanza Source #

The optional stanza type (test suite or benchmark), if it is one.

targetSelectorPluralPkgs :: TargetSelector -> Plural Source #

Does the TargetSelector potentially refer to one package or many?

targetSelectorRefersToPkgs :: TargetSelector -> Bool Source #

Does the TargetSelector refer to packages or to components?

reportTargetProblems :: Verbosity -> String -> [TargetProblem'] -> IO a Source #

Default implementation of reportTargetProblems simply renders one problem per line.

renderTargetProblem Source #

Arguments

:: String

verb

-> (a -> String)

how to render custom problems

-> TargetProblem a 
-> String 

Default implementation of renderTargetProblem.

renderTargetProblemNoneEnabled :: String -> TargetSelector -> [AvailableTarget ()] -> String Source #

Several commands have a TargetProblemNoneEnabled problem constructor. This renders an error message for those cases.

renderTargetProblemNoTargets :: String -> TargetSelector -> String Source #

Several commands have a TargetProblemNoTargets problem constructor. This renders an error message for those cases.

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