cmdargs-0.10.5: Command line argument processing

Safe HaskellNone

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).

Synopsis

Running command lines

process :: Mode a -> [String] -> Either String aSource

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 aSource

Process the flags obtained by getArgs and expandArgsAt 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. 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] -> aSource

Process a list of flags (usually obtained from getArgs and expandArgsAt) 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. This function does not take account of any environment variables that may be set (see processArgs).

Constructing command lines

type Name = StringSource

A name, either the name of a flag (--foo) or the name of a mode.

type Help = StringSource

A help message that goes with either a flag or a mode.

type FlagHelp = StringSource

The type of a flag, i.e. --foo=TYPE.

parseBool :: String -> Maybe BoolSource

Parse a boolean, accepts as True: true yes on enabled 1.

data Group a Source

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

groupUnnamed :: [a]

Normal items.

groupHidden :: [a]

Items that are hidden (not displayed in the help message).

groupNamed :: [(Help, [a])]

Items that have been grouped, along with a description of each group.

Instances

fromGroup :: Group a -> [a]Source

Convert a group into a list.

toGroup :: [a] -> Group aSource

Convert a list into a group, placing all fields in groupUnnamed.

data Mode a Source

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:

To produce the help information for a mode, either use helpText or show.

Constructors

Mode 

Fields

modeGroupModes :: Group (Mode a)

The available sub-modes

modeNames :: [Name]

The names assigned to this mode (for the root mode, this name is used as the program name)

modeValue :: a

Value to start with

modeCheck :: a -> Either String a

Check the value reprsented by a mode is correct, after applying all flags

modeReform :: a -> Maybe [String]

Given a value, try to generate the input arguments.

modeExpandAt :: Bool

Expand @ arguments with expandArgsAt, defaults to True, only applied if using an IO processing function. Only the root Modes value will be used.

modeHelp :: Help

Help text

modeHelpSuffix :: [String]

A longer help suffix displayed after a mode

modeArgs :: ([Arg a], Maybe (Arg a))

The unnamed arguments, a series of arguments, followed optionally by one for all remaining slots

modeGroupFlags :: Group (Flag a)

Groups of flags

Instances

modeModes :: Mode a -> [Mode a]Source

Extract the modes from a Mode

modeFlags :: Mode a -> [Flag a]Source

Extract the flags from a Mode

data FlagInfo Source

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

Constructors

FlagReq

Required argument

FlagOpt String

Optional argument

FlagOptRare String

Optional argument that requires an = before the value

FlagNone

No argument

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).

data Flag a Source

A flag, consisting of a list of flag names and other information.

Constructors

Flag 

Fields

flagNames :: [Name]

The names for the flag.

flagInfo :: FlagInfo

Information about a flag's arguments.

flagValue :: Update a

The way of processing a flag.

flagType :: FlagHelp

The type of data for the flag argument, i.e. FILE/DIR/EXT

flagHelp :: Help

The help message associated with this flag.

Instances

data Arg a Source

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 

Fields

argValue :: Update a

A way of processing the argument.

argType :: FlagHelp

The type of data for the argument, i.e. FILE/DIR/EXT

argRequire :: Bool

Is at least one of these arguments required, the command line will fail if none are set

Instances

Remap Arg 
Show (Arg a) 

checkMode :: Mode a -> Maybe StringSource

Check that a mode is well formed.

class Remap m whereSource

Methods

remapSource

Arguments

:: (a -> b)

Embed a value

-> (b -> (a, a -> b))

Extract the mode and give a way of re-embedding

-> m a 
-> m b 

Instances

remap2 :: Remap m => (a -> b) -> (b -> a) -> m a -> m bSource

remapUpdate :: Functor f => t -> (t1 -> (t2, a -> b)) -> (t3 -> t2 -> f a) -> t3 -> t1 -> f bSource

modeEmpty :: a -> Mode aSource

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 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 HelpFormatAll if there is not too much text, otherwise HelpFormatOne.

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] -> StringSource

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

data Complete Source

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

completeSource

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.