Portability | portable |
---|---|
Maintainer | cabal-devel@haskell.org |
Safe Haskell | Safe-Infered |
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
.
- data CommandUI flags = CommandUI {
- commandName :: String
- commandSynopsis :: String
- commandUsage :: String -> String
- commandDescription :: Maybe (String -> String)
- commandDefaultFlags :: flags
- commandOptions :: ShowOrParseArgs -> [OptionField flags]
- commandShowOptions :: CommandUI flags -> flags -> [String]
- data CommandParse flags
- = CommandHelp (String -> String)
- | CommandList [String]
- | CommandErrors [String]
- | CommandReadyToGo flags
- commandParseArgs :: CommandUI flags -> Bool -> [String] -> CommandParse (flags -> flags, [String])
- data ShowOrParseArgs
- makeCommand :: String -> String -> Maybe (String -> String) -> flags -> (ShowOrParseArgs -> [OptionField flags]) -> CommandUI flags
- data Command action
- commandAddAction :: CommandUI flags -> (flags -> [String] -> action) -> Command action
- noExtraFlags :: [String] -> IO ()
- commandsRun :: CommandUI a -> [Command action] -> [String] -> CommandParse (a, CommandParse action)
- data OptionField a = OptionField {
- optionName :: Name
- optionDescr :: [OptDescr a]
- type Name = String
- option :: SFlags -> LFlags -> Description -> get -> set -> MkOptDescr get set a -> OptionField a
- multiOption :: Name -> get -> set -> [get -> set -> OptDescr a] -> OptionField a
- liftOption :: (b -> a) -> (a -> b -> b) -> OptionField a -> OptionField b
- viewAsFieldDescr :: OptionField a -> FieldDescr a
- data OptDescr a
- = 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 Description = String
- type SFlags = [Char]
- type LFlags = [String]
- type OptFlags = (SFlags, LFlags)
- type ArgPlaceHolder = String
- type MkOptDescr get set a = SFlags -> LFlags -> Description -> get -> set -> OptDescr a
- reqArg :: Monoid b => ArgPlaceHolder -> ReadE b -> (b -> [String]) -> MkOptDescr (a -> b) (b -> a -> a) a
- reqArg' :: Monoid b => ArgPlaceHolder -> (String -> b) -> (b -> [String]) -> MkOptDescr (a -> b) (b -> a -> a) a
- optArg :: Monoid b => ArgPlaceHolder -> ReadE b -> b -> (b -> [Maybe String]) -> MkOptDescr (a -> b) (b -> a -> a) a
- optArg' :: Monoid b => ArgPlaceHolder -> (Maybe String -> b) -> (b -> [Maybe String]) -> MkOptDescr (a -> b) (b -> a -> a) a
- noArg :: (Eq b, Monoid b) => b -> MkOptDescr (a -> b) (b -> a -> a) a
- boolOpt :: (b -> Maybe Bool) -> (Bool -> b) -> SFlags -> SFlags -> MkOptDescr (a -> b) (b -> a -> a) a
- boolOpt' :: (b -> Maybe Bool) -> (Bool -> b) -> OptFlags -> OptFlags -> MkOptDescr (a -> b) (b -> a -> a) a
- choiceOpt :: Eq b => [(b, OptFlags, Description)] -> MkOptDescr (a -> b) (b -> a -> a) a
- choiceOptFromEnum :: (Bounded b, Enum b, Show b, Eq b) => MkOptDescr (a -> b) (b -> a -> a) a
Command interface
CommandUI | |
|
commandShowOptions :: CommandUI flags -> flags -> [String]Source
Show flags in the standard long option command line format
data CommandParse flags Source
CommandHelp (String -> String) | |
CommandList [String] | |
CommandErrors [String] | |
CommandReadyToGo flags |
:: CommandUI flags | |
-> Bool | Is the command a global or subcommand? |
-> [String] | |
-> CommandParse (flags -> flags, [String]) |
Parse a bunch of command line arguments
Constructing commands
:: String | name |
-> String | short description |
-> Maybe (String -> String) | long description |
-> flags | initial/empty flags |
-> (ShowOrParseArgs -> [OptionField flags]) | options |
-> CommandUI flags |
Make a Command from standard GetOpt
options.
Associating actions with commands
commandAddAction :: CommandUI flags -> (flags -> [String] -> action) -> Command actionSource
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.
Running commands
commandsRun :: CommandUI a -> [Command action] -> [String] -> CommandParse (a, CommandParse action)Source
Option Fields
data OptionField a Source
We usually have a datatype 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 datatype.
OptionField | |
|
Constructing Option Fields
option :: SFlags -> LFlags -> Description -> get -> set -> MkOptDescr get set a -> OptionField aSource
Create an option taking a single OptDescr. No explicit Name is given for the Option, the name is the first LFlag given.
:: 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 bSource
viewAsFieldDescr :: OptionField a -> FieldDescr aSource
to view as a FieldDescr, we sort the list of interfaces (Req > Bool > Choice > Opt) and consider only the first one.
Option Descriptions
An OptionField takes one or more OptDescrs, describing the command line interface for the field.
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 Description = StringSource
type ArgPlaceHolder = StringSource
OptDescr smart
constructors
type MkOptDescr get set a = SFlags -> LFlags -> Description -> get -> set -> OptDescr aSource
reqArg :: Monoid b => ArgPlaceHolder -> ReadE b -> (b -> [String]) -> MkOptDescr (a -> b) (b -> a -> a) aSource
Create a string-valued command line interface.
reqArg' :: Monoid b => ArgPlaceHolder -> (String -> b) -> (b -> [String]) -> MkOptDescr (a -> b) (b -> a -> a) aSource
(String -> a) variant of reqArg
optArg :: Monoid b => ArgPlaceHolder -> ReadE b -> b -> (b -> [Maybe String]) -> MkOptDescr (a -> b) (b -> a -> a) aSource
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) aSource
(String -> a) variant of optArg
noArg :: (Eq b, Monoid b) => b -> MkOptDescr (a -> b) (b -> a -> a) aSource
boolOpt :: (b -> Maybe Bool) -> (Bool -> b) -> SFlags -> SFlags -> MkOptDescr (a -> b) (b -> a -> a) aSource
boolOpt' :: (b -> Maybe Bool) -> (Bool -> b) -> OptFlags -> OptFlags -> MkOptDescr (a -> b) (b -> a -> a) aSource
choiceOpt :: Eq b => [(b, OptFlags, Description)] -> MkOptDescr (a -> b) (b -> a -> a) aSource
create a Choice option
choiceOptFromEnum :: (Bounded b, Enum b, Show b, Eq b) => MkOptDescr (a -> b) (b -> a -> a) aSource
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.