| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
System.Console.CmdArgs.Explicit
Contents
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
       xs <- processArgs arguments
       if ("help","") `elem` xs then
           print $ helpText [] HelpFormatDefault arguments
        else
           print xs
   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.
Parsing rules: Command lines are parsed as per most GNU programs. Short arguments single
    letter flags start with -, longer flags start with --, and everything else is considered
    an argument. Anything after -- alone is considered to be an argument. For example:
-f --flag argument1 -- --argument2
This command line passes one single letter flag (f), one longer flag (flag) and two arguments
    (argument1 and --argument2).
- process :: Mode a -> [String] -> Either String a
- processArgs :: Mode a -> IO a
- processValue :: Mode a -> [String] -> a
- processValueIO :: Mode a -> [String] -> 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 {- modeGroupModes :: Group (Mode a)
- modeNames :: [Name]
- modeValue :: a
- modeCheck :: a -> Either String a
- modeReform :: a -> Maybe [String]
- modeExpandAt :: Bool
- modeHelp :: Help
- modeHelpSuffix :: [String]
- modeArgs :: ([Arg a], Maybe (Arg a))
- modeGroupFlags :: Group (Flag a)
 
- 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
- remap2 :: Remap m => (a -> b) -> (b -> a) -> m a -> m b
- remapUpdate :: (a -> b) -> (b -> (a, a -> b)) -> Update a -> Update b
- modeEmpty :: a -> Mode a
- 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
- flagNumericVersion :: (a -> a) -> Flag a
- flagsVerbosity :: (Verbosity -> a -> a) -> [Flag a]
- data HelpFormat
- helpText :: [String] -> HelpFormat -> Mode a -> [Text]
- expandArgsAt :: [String] -> IO [String]
- splitArgs :: String -> [String]
- joinArgs :: [String] -> String
- data Complete
- complete :: Mode a -> [String] -> (Int, Int) -> [Complete]
Running command lines
process :: Mode a -> [String] -> Either String a Source #
Process a list of flags (usually obtained from getArgs/expandArgsAt) with a mode. Returns
   Left and an error message if the command line fails to parse, or Right and
   the associated value.
processArgs :: Mode a -> IO a Source #
Process the flags obtained by getArgsexpandArgsAtprocess. This function makes
   use of the following environment variables:
- $CMDARGS_COMPLETE- causes the program to produce completions using- complete, then exit. Completions are based on the result of- getArgs, the index of the current argument is taken from- $CMDARGS_COMPLETE(set it to- -to complete the last argument), and the index within that argument is taken from- $CMDARGS_COMPLETE_POS(if set).
- $CMDARGS_HELPER/- $CMDARGS_HELPER_PROG- uses the helper mechanism for entering command line programs as described in System.Console.CmdArgs.Helper.
processValue :: Mode a -> [String] -> a Source #
Process a list of flags (usually obtained from getArgsexpandArgsAtprocess. This function
   does not take account of any environment variables that may be set
   (see processArgs).
If you are in IO you will probably get a better user experience by calling processValueIO.
processValueIO :: Mode a -> [String] -> IO a Source #
Like processValue but on failure prints to stderr and exits the program.
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 a Source #
Convert a list into a group, placing all fields in groupUnnamed.
A mode. Do not use the Mode constructor directly, instead
   use mode to construct the Mode and then record updates.
   Each mode has three main features:
- A list of submodes (modeGroupModes)
- A list of flags (modeGroupFlags)
- Optionally an unnamed argument (modeArgs)
To produce the help information for a mode, either use helpText or show.
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 -> String Source #
Extract the value from inside a FlagOpt or FlagOptRare, or raises an error.
type Update a = String -> a -> Either String a Source #
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 | |
Like functor, but where the the argument isn't just covariant.
Minimal complete definition
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 | 
Convert between two values.
remap2 :: Remap m => (a -> b) -> (b -> a) -> m a -> m b Source #
Restricted version of remap where the values are isomorphic.
remapUpdate :: (a -> b) -> (b -> (a, a -> b)) -> Update a -> Update b Source #
modeEmpty :: a -> Mode a Source #
Create an empty mode specifying only modeValue. All other fields will usually be populated
   using record updates.
mode :: Name -> a -> Help -> Arg a -> [Flag a] -> Mode a Source #
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 a Source #
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 a Source #
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 a Source #
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 a Source #
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 a Source #
Create an argument flag, with an update function and the type of the argument.
flagBool :: [Name] -> (Bool -> a -> a) -> Help -> Flag a Source #
Create a boolean flag, with a list of flag names, an update function and some help text.
flagHelpSimple :: (a -> a) -> Flag a Source #
Create a help flag triggered by -?/--help.
flagHelpFormat :: (HelpFormat -> TextFormat -> a -> a) -> Flag a Source #
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 a Source #
Create a version flag triggered by -V/--version.
flagNumericVersion :: (a -> a) -> Flag a Source #
Create a version flag triggered by --numeric-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. | 
| HelpFormatBash | Bash completion information | 
| HelpFormatZsh | Z shell completion information | 
helpText :: [String] -> HelpFormat -> Mode a -> [Text] Source #
Generate a help message from a mode.  The first argument is a prefix,
   which is prepended when not using HelpFormatBash or HelpFormatZsh.
Utilities for working with command lines
expandArgsAt :: [String] -> IO [String] Source #
Expand @ directives in a list of arguments, usually obtained from getArgs.
   As an example, given the file test.txt with the lines hello and world:
expandArgsAt ["@test.txt","!"] == ["hello","world","!"]
Any @ directives in the files will be recursively expanded (raising an error
   if there is infinite recursion).
To supress @ expansion, pass any @ arguments after --.
splitArgs :: String -> [String] Source #
Given a string, split into the available arguments. The inverse of joinArgs.
joinArgs :: [String] -> String Source #
Given a sequence of arguments, join them together in a manner that could be used on
   the command line, giving preference to the Windows cmd shell quoting conventions.
For an alternative version, intended for actual running the result in a shell, see "System.Process.showCommandForUser"
How to complete a command line option.
   The Show instance is suitable for parsing from shell scripts.
Constructors
| CompleteValue String | Complete to a particular value | 
| CompleteFile String FilePath | Complete to a prefix, and a file | 
| CompleteDir String FilePath | Complete to a prefix, and a directory | 
Arguments
| :: Mode a | Mode specifying which arguments are allowed | 
| -> [String] | Arguments the user has already typed | 
| -> (Int, Int) | 0-based index of the argument they are currently on, and the position in that argument | 
| -> [Complete] | 
Given a current state, return the set of commands you could type now, in preference order.