Cabal-1.6.0.3: A framework for packaging Haskell softwareSource codeContentsIndex
Distribution.Simple.Command
Portabilityportable
Maintainercabal-devel@haskell.org
Contents
Command interface
Constructing commands
Associating actions with commands
Running commands
Option Fields
Constructing Option Fields
Liftings & Projections
Option Descriptions
OptDescr smart constructors
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
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 ShowOrParseArgs
= ShowArgs
| ParseArgs
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 ()
data CommandParse flags
= CommandHelp (String -> String)
| CommandList [String]
| CommandErrors [String]
| CommandReadyToGo flags
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
data CommandUI flags Source
Constructors
CommandUI
commandName :: StringThe name of the command as it would be entered on the command line. For example "build".
commandSynopsis :: StringA short, one line description of the command to use in help texts.
commandUsage :: String -> StringThe useage line summary for this command
commandDescription :: Maybe (String -> String)Additional explanation of the command to use in help texts.
commandDefaultFlags :: flagsInitial / 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
Constructing commands
data ShowOrParseArgs Source
Constructors
ShowArgs
ParseArgs
makeCommandSource
::
=> Stringname
-> Stringshort description
-> Maybe (String -> String)long description
-> flagsinitial/empty flags
-> ShowOrParseArgs -> [OptionField flags]options
-> CommandUI flags
Make a Command from standard GetOpt options.
Associating actions with commands
data Command action Source
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
data CommandParse flags Source
Constructors
CommandHelp (String -> String)
CommandList [String]
CommandErrors [String]
CommandReadyToGo flags
show/hide Instances
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.
Constructors
OptionField
optionName :: Name
optionDescr :: [OptDescr a]
type Name = StringSource
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.
multiOptionSource
::
=> 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
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 Description = StringSource
type SFlags = [Char]Source
Short command line option strings
type LFlags = [String]Source
Long command line option strings
type OptFlags = (SFlags, LFlags)Source
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.
Produced by Haddock version 2.4.2