Cabal-1.23.1.0: A framework for packaging Haskell software

CopyrightDuncan Coutts 2007
LicenseBSD3
Maintainercabal-devel@haskell.org
Portabilitynon-portable (ExistentialQuantification)
Safe HaskellNone
LanguageHaskell98

Distribution.Simple.Command

Contents

Description

This is to do with command line handling. The Cabal command line is organised into a number of named sub-commands (much like darcs). The CommandUI abstraction represents one of these sub-commands, with a name, description, a set of flags. Commands can be associated with actions and run. It handles some common stuff automatically, like the --help and command line completion flags. It is designed to allow other tools make derived commands. This feature is used heavily in cabal-install.

Synopsis

Command interface

data CommandUI flags Source

Constructors

CommandUI 

Fields

commandName :: String

The name of the command as it would be entered on the command line. For example "build".

commandSynopsis :: String

A short, one line description of the command to use in help texts.

commandUsage :: String -> String

A function that maps a program name to a usage summary for this command.

commandDescription :: Maybe (String -> String)

Additional explanation of the command to use in help texts.

commandNotes :: Maybe (String -> String)

Post-Usage notes and examples in help texts

commandDefaultFlags :: flags

Initial / empty flags

commandOptions :: ShowOrParseArgs -> [OptionField flags]

All the Option fields for this command

commandShowOptions :: CommandUI flags -> flags -> [String] Source

Show flags in the standard long option command line format

commandParseArgs Source

Arguments

:: CommandUI flags 
-> Bool

Is the command a global or subcommand?

-> [String] 
-> CommandParse (flags -> flags, [String]) 

Parse a bunch of command line arguments

getNormalCommandDescriptions :: [Command action] -> [(String, String)] Source

Helper function for creating globalCommand description

Constructing commands

usageDefault :: String -> String -> String Source

Default "usage" documentation text for commands.

usageAlternatives :: String -> [String] -> String -> String Source

Create "usage" documentation from a list of parameter configurations.

mkCommandUI Source

Arguments

:: String

name

-> String

synopsis

-> [String]

usage alternatives

-> flags

initial/empty flags

-> (ShowOrParseArgs -> [OptionField flags])

options

-> CommandUI flags 

Make a Command from standard GetOpt options.

hiddenCommand :: Command action -> Command action Source

Mark command as hidden. Hidden commands don't show up in the 'progname help' or 'progname --help' output.

Associating actions with commands

data Command action Source

commandAddAction :: CommandUI flags -> (flags -> [String] -> action) -> Command action Source

noExtraFlags :: [String] -> IO () Source

Utility function, many commands do not accept additional flags. This action fails with a helpful error message if the user supplies any extra.

Building lists of commands

data CommandSpec action Source

wraps a CommandUI together with a function that turns it into a Command. By hiding the type of flags for the UI allows construction of a list of all UIs at the top level of the program. That list can then be used for generation of manual page as well as for executing the selected command.

Constructors

forall flags . CommandSpec (CommandUI flags) (CommandUI flags -> Command action) CommandType 

Running commands

commandsRun :: CommandUI a -> [Command action] -> [String] -> CommandParse (a, CommandParse action) Source

Option Fields

data OptionField a Source

We usually have a data type for storing configuration values, where every field stores a configuration option, and the user sets the value either via command line flags or a configuration file. An individual OptionField models such a field, and we usually build a list of options associated to a configuration data type.

Constructors

OptionField 

Fields

optionName :: Name
 
optionDescr :: [OptDescr a]
 

Constructing Option Fields

option :: SFlags -> LFlags -> Description -> get -> set -> MkOptDescr get set a -> OptionField a Source

Create an option taking a single OptDescr. No explicit Name is given for the Option, the name is the first LFlag given.

multiOption Source

Arguments

:: Name 
-> get 
-> set 
-> [get -> set -> OptDescr a]

MkOptDescr constructors partially applied to flags and description.

-> OptionField a 

Create an option taking several OptDescrs. You will have to give the flags and description individually to the OptDescr constructor.

Liftings & Projections

liftOption :: (b -> a) -> (a -> b -> b) -> OptionField a -> OptionField b Source

viewAsFieldDescr :: OptionField a -> FieldDescr a Source

to view as a FieldDescr, we sort the list of interfaces (Req > Bool > Choice > Opt) and consider only the first one.

Option Descriptions

data OptDescr a Source

An OptionField takes one or more OptDescrs, describing the command line interface for the field.

Constructors

ReqArg Description OptFlags ArgPlaceHolder (ReadE (a -> a)) (a -> [String]) 
OptArg Description OptFlags ArgPlaceHolder (ReadE (a -> a)) (a -> a) (a -> [Maybe String]) 
ChoiceOpt [(Description, OptFlags, a -> a, a -> Bool)] 
BoolOpt Description OptFlags OptFlags (Bool -> a -> a) (a -> Maybe Bool) 

type SFlags = [Char] Source

Short command line option strings

type LFlags = [String] Source

Long command line option strings

OptDescr smart constructors

type MkOptDescr get set a = SFlags -> LFlags -> Description -> get -> set -> OptDescr a Source

reqArg :: Monoid b => ArgPlaceHolder -> ReadE b -> (b -> [String]) -> MkOptDescr (a -> b) (b -> a -> a) a Source

Create a string-valued command line interface.

reqArg' :: Monoid b => ArgPlaceHolder -> (String -> b) -> (b -> [String]) -> MkOptDescr (a -> b) (b -> a -> a) a Source

(String -> a) variant of "reqArg"

optArg :: Monoid b => ArgPlaceHolder -> ReadE b -> b -> (b -> [Maybe String]) -> MkOptDescr (a -> b) (b -> a -> a) a Source

Create a string-valued command line interface with a default value.

optArg' :: Monoid b => ArgPlaceHolder -> (Maybe String -> b) -> (b -> [Maybe String]) -> MkOptDescr (a -> b) (b -> a -> a) a Source

(String -> a) variant of "optArg"

noArg :: Eq b => b -> MkOptDescr (a -> b) (b -> a -> a) a Source

boolOpt :: (b -> Maybe Bool) -> (Bool -> b) -> SFlags -> SFlags -> MkOptDescr (a -> b) (b -> a -> a) a Source

boolOpt' :: (b -> Maybe Bool) -> (Bool -> b) -> OptFlags -> OptFlags -> MkOptDescr (a -> b) (b -> a -> a) a Source

choiceOpt :: Eq b => [(b, OptFlags, Description)] -> MkOptDescr (a -> b) (b -> a -> a) a Source

create a Choice option

choiceOptFromEnum :: (Bounded b, Enum b, Show b, Eq b) => MkOptDescr (a -> b) (b -> a -> a) a Source

create a Choice option out of an enumeration type. As long flags, the Show output is used. As short flags, the first character which does not conflict with a previous one is used.