System.Console.CmdArgs.Explicit
Description
This module constructs command lines. You may either use the helper functions
(flagNone, flagOpt, mode etc.) or construct the type directly. These
types are intended to give all the necessary power to the person constructing
a command line parser.
For people constructing simpler command line parsers, the module System.Console.CmdArgs.Implicit may be more appropriate.
As an example of a parser:
arguments :: Mode [(String,String)]
arguments = mode "explicit" [] "Explicit sample program" (flagArg (upd "file") "FILE")
[flagOpt "world" ["hello","h"] (upd "world") "WHO" "World argument"
,flagReq ["greeting","g"] (upd "greeting") "MSG" "Greeting to give"
,flagHelpSimple (("help",""):)]
where upd msg x v = Right $ (msg,x):v
And this can be invoked by:
main = do
x <- processArgs arguments
if ("help","") `elem` xs then
print $ helpText def arguments
else
print x
Groups: The Group structure allows flags/modes to be grouped for the purpose of
displaying help. When processing command lines, the group structure is ignored.
Modes: The Explicit module allows multiple mode programs by placing additional modes
in modeGroupModes. Every mode is allowed sub-modes, and thus multiple levels of mode
may be created. Given a mode x with sub-modes xs, if the first argument corresponds
to the name of a sub-mode, then that sub-mode will be applied. If not, then the arguments
will be processed by mode x. Consequently, if you wish to force the user to explicitly
enter a mode, simply give sub-modes, and leave modeArgs as Nothing. Alternatively, if
you want one sub-mode to be selected by default, place all it's flags both in the sub-mode
and the outer mode.
- process :: Mode a -> [String] -> Either String a
- processValue :: Mode a -> [String] -> a
- processArgs :: Mode a -> IO a
- type Name = String
- type Help = String
- type FlagHelp = String
- parseBool :: String -> Maybe Bool
- data Group a = Group {
- groupUnnamed :: [a]
- groupHidden :: [a]
- groupNamed :: [(Help, [a])]
- fromGroup :: Group a -> [a]
- toGroup :: [a] -> Group a
- data Mode a = Mode {}
- modeModes :: Mode a -> [Mode a]
- modeFlags :: Mode a -> [Flag a]
- data FlagInfo
- fromFlagOpt :: FlagInfo -> String
- type Update a = String -> a -> Either String a
- data Flag a = Flag {}
- data Arg a = Arg {}
- checkMode :: Mode a -> Maybe String
- class Remap m where
- remap :: (a -> b) -> (b -> (a, a -> b)) -> m a -> m b
- remap2 :: Remap m => (a -> b) -> (b -> a) -> m a -> m b
- mode :: Name -> a -> Help -> Arg a -> [Flag a] -> Mode a
- modes :: String -> a -> Help -> [Mode a] -> Mode a
- flagNone :: [Name] -> (a -> a) -> Help -> Flag a
- flagOpt :: String -> [Name] -> Update a -> FlagHelp -> Help -> Flag a
- flagReq :: [Name] -> Update a -> FlagHelp -> Help -> Flag a
- flagArg :: Update a -> FlagHelp -> Arg a
- flagBool :: [Name] -> (Bool -> a -> a) -> Help -> Flag a
- flagHelpSimple :: (a -> a) -> Flag a
- flagHelpFormat :: (HelpFormat -> TextFormat -> a -> a) -> Flag a
- flagVersion :: (a -> a) -> Flag a
- flagsVerbosity :: (Verbosity -> a -> a) -> [Flag a]
- data HelpFormat
- helpText :: HelpFormat -> Mode a -> [Text]
Running command lines
process :: Mode a -> [String] -> Either String aSource
Process a list of flags (usually obtained from getArgs) with a mode. Returns
Left and an error message if the command line fails to parse, or Right and
the associated value.
processValue :: Mode a -> [String] -> aSource
Process a list of flags (usually obtained from getArgs) with a mode. Displays
an error and exits with failure if the command line fails to parse, or returns
the associated value. Implemeneted in terms of process.
processArgs :: Mode a -> IO aSource
Process the flags obtained by getArgs with a mode. Displays
an error and exits with failure if the command line fails to parse, or returns
the associated value. Implemented in terms of process.
Constructing command lines
A group of items (modes or flags). The items are treated as a list, but the group structure is used when displaying the help message.
Constructors
| Group | |
Fields
| |
toGroup :: [a] -> Group aSource
Convert a list into a group, placing all fields in groupUnnamed.
A mode. Each mode has three main features:
- A list of submodes (
modeGroupModes) - A list of flags (
modeGroupFlags) - Optionally an unnamed argument (
modeArgs)
Constructors
| Mode | |
Fields
| |
The FlagInfo type has the following meaning:
FlagReq FlagOpt FlagOptRare/FlagNone -xfoo -x=foo -x=foo -x= -foo -x foo -x=foo -x foo -x= foo -x=foo -x=foo -x=foo -x=foo --xx foo --xx=foo --xx foo --xx foo --xx=foo --xx=foo --xx=foo --xx=foo
fromFlagOpt :: FlagInfo -> StringSource
Extract the value from inside a FlagOpt or FlagOptRare, or raises an error.
type Update a = String -> a -> Either String aSource
A function to take a string, and a value, and either produce an error message
(Left), or a modified value (Right).
A flag, consisting of a list of flag names and other information.
Constructors
| Flag | |
An unnamed argument. Anything not starting with - is considered an argument,
apart from "-" which is considered to be the argument "-", and any arguments
following "--". For example:
programname arg1 -j - --foo arg3 -- -arg4 --arg5=1 arg6
Would have the arguments:
["arg1","-","arg3","-arg4","--arg5=1","arg6"]
Constructors
| Arg | |
Methods
Arguments
| :: (a -> b) | Embed a value |
| -> (b -> (a, a -> b)) | Extract the mode and give a way of re-embedding |
| -> m a | |
| -> m b |
mode :: Name -> a -> Help -> Arg a -> [Flag a] -> Mode aSource
Create a mode with a name, an initial value, some help text, a way of processing arguments and a list of flags.
modes :: String -> a -> Help -> [Mode a] -> Mode aSource
Create a list of modes, with a program name, an initial value, some help text and the child modes.
flagNone :: [Name] -> (a -> a) -> Help -> Flag aSource
Create a flag taking no argument value, with a list of flag names, an update function and some help text.
flagOpt :: String -> [Name] -> Update a -> FlagHelp -> Help -> Flag aSource
Create a flag taking an optional argument value, with an optional value, a list of flag names, an update function, the type of the argument and some help text.
flagReq :: [Name] -> Update a -> FlagHelp -> Help -> Flag aSource
Create a flag taking a required argument value, with a list of flag names, an update function, the type of the argument and some help text.
flagArg :: Update a -> FlagHelp -> Arg aSource
Create an argument flag, with an update function and the type of the argument.
flagBool :: [Name] -> (Bool -> a -> a) -> Help -> Flag aSource
Create a boolean flag, with a list of flag names, an update function and some help text.
flagHelpSimple :: (a -> a) -> Flag aSource
Create a help flag triggered by -?/--help.
flagHelpFormat :: (HelpFormat -> TextFormat -> a -> a) -> Flag aSource
Create a help flag triggered by -?/--help. The user
may optionally modify help by specifying the format, such as:
--help=all - help for all modes --help=html - help in HTML format --help=100 - wrap the text at 100 characters --help=100,one - full text wrapped at 100 characters
flagVersion :: (a -> a) -> Flag aSource
Create a version flag triggered by -V/--version.
flagsVerbosity :: (Verbosity -> a -> a) -> [Flag a]Source
Create verbosity flags triggered by -v/--verbose and
-q/--quiet
Displaying help
data HelpFormat Source
Specify the format to output the help.
Constructors
| HelpFormatDefault | Equivalent to |
| HelpFormatOne | Display only the first mode. |
| HelpFormatAll | Display all modes. |
helpText :: HelpFormat -> Mode a -> [Text]Source
Generate a help message from a mode.