Copyright | (c) 2007 Bart Massey |
---|---|
License | BSD-style (see the file COPYING) |
Maintainer | Bart Massey <bart.massey@gmail.com> |
Stability | stable |
Portability | portable |
Safe Haskell | Safe |
Language | Haskell98 |
ParseArgs
is a full-featured command-line argument
parsing library.
This module supplies an argument parser. Given a
description of type [Arg
] of the legal arguments to the
program, a list of argument strings, and a bit of extra
information, the parseArgs
function in this module
returns an Args
data structure suitable for querying
using the provided functions gotArg
, getArg
, etc.
Synopsis
- data Ord a => Arg a = Arg {}
- data Argtype
- = ArgtypeString (Maybe String)
- | ArgtypeInteger (Maybe Integer)
- | ArgtypeInt (Maybe Int)
- | ArgtypeDouble (Maybe Double)
- | ArgtypeFloat (Maybe Float)
- data ArgsComplete
- data ArgsDash
- class APCData a where
- getAPCData :: a -> ArgsParseControl
- data ArgsParseControl = ArgsParseControl {}
- data DataArg
- argDataRequired :: String -> (Maybe a -> Argtype) -> Maybe DataArg
- argDataOptional :: String -> (Maybe a -> Argtype) -> Maybe DataArg
- argDataDefaulted :: String -> (Maybe a -> Argtype) -> a -> Maybe DataArg
- data Ord a => Args a = Args {}
- parseArgs :: (Show a, Ord a, APCData b) => b -> [Arg a] -> String -> [String] -> Args a
- parseArgsIO :: (Show a, Ord a, APCData b) => b -> [Arg a] -> IO (Args a)
- gotArg :: Ord a => Args a -> a -> Bool
- class ArgType b where
- getArgString :: (Show a, Ord a) => Args a -> a -> Maybe String
- getArgFile :: (Show a, Ord a) => Args a -> a -> IOMode -> IO (Maybe Handle)
- getArgStdio :: (Show a, Ord a) => Args a -> a -> IOMode -> IO Handle
- getArgInteger :: (Show a, Ord a) => Args a -> a -> Maybe Integer
- getArgInt :: (Show a, Ord a) => Args a -> a -> Maybe Int
- getArgDouble :: (Show a, Ord a) => Args a -> a -> Maybe Double
- getArgFloat :: (Show a, Ord a) => Args a -> a -> Maybe Float
- newtype ArgFileOpener = ArgFileOpener {
- argFileOpener :: IOMode -> IO Handle
- data ParseArgsException = ParseArgsException String String
- baseName :: String -> String
- parseError :: String -> String -> a
- usageError :: Ord a => Args a -> String -> b
- data IOMode
Describing allowed arguments
The argument parser requires a description of
the arguments that will be parsed. This is
supplied as a list of Arg
records, built up
using the functions described here.
The description of an argument, suitable for
messages and for parsing. The argData
field
is used both for flags with a data argument, and
for positional data arguments.
There are two cases:
- The argument is a flag, in which case at least
one of
argAbbr
andargName
is provided; - The argument is positional, in which case neither
argAbbr
norargName
are provided, butargData
is.
If none of argAbbr
, argName
, or argData
are
provided, this is an error. See also the
argDataRequired
, argDataOptional
, and
argDataDefaulted
functions below, which are used to
generate argData
.
The types of an argument carrying data. The constructor argument is used to carry a default value.
The constructor argument should really be hidden.
Values of this type are normally constructed within
the pseudo-constructors pseudo-constructors
argDataRequired
, argDataOptional
, and
argDataDefaulted
, to which only the constructor
function itself is passed.
data ArgsComplete Source #
How "sloppy" the parse is.
ArgsComplete | Any extraneous arguments (unparseable from description) will cause the parser to fail. |
ArgsTrailing String | Trailing extraneous arguments are permitted, and will be skipped, saved, and returned. The constructor argument is the name of the args. |
ArgsInterspersed | All extraneous arguments are permitted, and will be skipped, saved, and returned. |
Instances
APCData ArgsComplete Source # | |
Defined in System.Console.ParseArgs |
Whether to always treat an unknown argument beginning with "-" as an error, or to allow it to be used as a positional argument when possible.
ArgsHardDash | If an argument begins with a "-", it will always be treated as an error unless it corresponds to a flag description. |
ArgsSoftDash | If an argument beginning with a "-" is unrecognized as a flag, treat it as a positional argument if possible. Otherwise it is an error. |
class APCData a where Source #
Class for building parse control information, for backward compatibility.
:: a | |
-> ArgsParseControl | Build an |
Instances
APCData ArgsParseControl Source # | |
Defined in System.Console.ParseArgs | |
APCData ArgsComplete Source # | |
Defined in System.Console.ParseArgs |
data ArgsParseControl Source #
Record containing the collective parse control information.
ArgsParseControl | |
|
Instances
APCData ArgsParseControl Source # | |
Defined in System.Console.ParseArgs |
DataArg and its pseudo-constructors
Information specific to an argument carrying a datum. This
is an opaque type, whose instances are constructed using the
pseudo-constructors argDataRequired
, argDataOptional
,
and argDataDefaulted
.
:: String | Datum print name. |
-> (Maybe a -> Argtype) | Type constructor for datum. |
-> Maybe DataArg | Result is |
Generate the argData
for the given non-optional argument.
:: String | Datum print name. |
-> (Maybe a -> Argtype) | Type constructor for datum. |
-> Maybe DataArg | Result is |
Generate the argData
for the given optional argument with no default.
:: String | Datum print name. |
-> (Maybe a -> Argtype) | Type constructor for datum. |
-> a | Datum default value. |
-> Maybe DataArg | Result is |
Generate the argData
for the given optional argument with the
given default.
Argument processing
The argument descriptions are used to parse the command line arguments, and the results of the parse can later be (efficiently) queried to determine program behavior.
Getting parse results
The argument parser returns an opaque map from argument index to parsed argument data (plus some convenience information).
The data structure parseArgs
produces. There is a should-be-hidden
field that describes the parse.
Args | |
|
:: (Show a, Ord a, APCData b) | |
=> b | Degree of completeness of parse. |
-> [Arg a] | Argument descriptions. |
-> IO (Args a) | Argument parse results. |
Most of the time, you just want the environment's
arguments and are willing to live in the IO monad.
This version of parseArgs
digs the pathname and arguments
out of the system directly.
Using parse results
Query functions permit checking for the existence and values of command-line arguments.
:: Ord a | |
=> Args a | Parsed arguments. |
-> a | Index of argument to be checked for. |
-> Bool | True if the arg was present. |
Check whether a given optional argument was supplied. Works on all types.
class ArgType b where Source #
Type of values that can be parsed by the argument parser.
:: (Show a, Ord a) | |
=> Args a | Parsed arguments. |
-> a | Index of argument to be retrieved. |
-> Maybe b | Argument value if present. |
Fetch an argument's value if it is present.
:: (Show a, Ord a) | |
=> Args a | Parsed arguments. |
-> a | Index of argument to be retrieved. |
-> b | Argument value. |
Fetch the value of a required argument.
Instances
ArgType Double Source # | |
ArgType Float Source # | |
ArgType Int Source # | |
ArgType Integer Source # | |
ArgType () Source # | |
ArgType ArgFileOpener Source # | |
Defined in System.Console.ParseArgs getArg :: (Show a, Ord a) => Args a -> a -> Maybe ArgFileOpener Source # getRequiredArg :: (Show a, Ord a) => Args a -> a -> ArgFileOpener Source # | |
ArgType [Char] Source # | |
:: (Show a, Ord a) | |
=> Args a | Parsed arguments. |
-> a | Index of argument to be retrieved. |
-> Maybe String | Argument value if present. |
- Deprecated
- Return the
String
value, if any, of the given argument.
:: (Show a, Ord a) | |
=> Args a | Parsed arguments. |
-> a | Index of argument to be retrieved. |
-> IOMode | IO mode the file should be opened in. |
-> IO (Maybe Handle) | Handle of opened file, if the argument was present. |
- Deprecated
- Treat the
String
value, if any, of the given argument as a file handle and try to open it as requested.
:: (Show a, Ord a) | |
=> Args a | Parsed arguments. |
-> a | Index of argument to be retrieved. |
-> Maybe Integer | Argument value if present. |
- Deprecated
- Return the
Integer
value, if any, of the given argument.
:: (Show a, Ord a) | |
=> Args a | Parsed arguments. |
-> a | Index of argument to be retrieved. |
-> Maybe Int | Argument value if present. |
- Deprecated
- Return the
Int
value, if any, of the given argument.
:: (Show a, Ord a) | |
=> Args a | Parsed arguments. |
-> a | Index of argument to be retrieved. |
-> Maybe Double | Argument value if present. |
- Deprecated
- Return the
Double
value, if any, of the given argument.
:: (Show a, Ord a) | |
=> Args a | Parsed arguments. |
-> a | Index of argument to be retrieved. |
-> Maybe Float | Argument value if present. |
- Deprecated
- Return the
Float
value, if any, of the given argument.
newtype ArgFileOpener Source #
ArgType
instance for opening a file from its string name.
ArgFileOpener | |
|
Instances
ArgType ArgFileOpener Source # | |
Defined in System.Console.ParseArgs getArg :: (Show a, Ord a) => Args a -> a -> Maybe ArgFileOpener Source # getRequiredArg :: (Show a, Ord a) => Args a -> a -> ArgFileOpener Source # |
Misc
data ParseArgsException Source #
This exception is raised with an appropriate error message when argument parsing fails. The first argument is the usage message, the second the actual error message from the parser.
Instances
Eq ParseArgsException Source # | |
Defined in System.Console.ParseArgs (==) :: ParseArgsException -> ParseArgsException -> Bool # (/=) :: ParseArgsException -> ParseArgsException -> Bool # | |
Show ParseArgsException Source # | |
Defined in System.Console.ParseArgs showsPrec :: Int -> ParseArgsException -> ShowS # show :: ParseArgsException -> String # showList :: [ParseArgsException] -> ShowS # | |
Exception ParseArgsException Source # | |
Defined in System.Console.ParseArgs |
Return the filename part of a pathname. Unnecessarily efficient implementation does a single tail-call traversal with no construction.
Generate a usage error with the given supplementary message string.
usageError :: Ord a => Args a -> String -> b Source #
Generate a usage error with the given supplementary message string.