Safe Haskell | None |
---|
This module provides simple command line argument processing.
The main function of interest is cmdArgs
.
A simple example is:
data Sample = Sample {hello :: String} deriving (Show, Data, Typeable)
sample = Sample{hello =def
&=
help
"World argument"&=
opt
"world"}&=
summary
"Sample v1"
main = print =<< cmdArgs
sample
Attributes are used to control a number of behaviours:
- The help message:
help
,typ
,details
,summary
,program
,groupname
- Flag behaviour:
opt
,enum
,verbosity
,ignore
- Flag name assignment:
name
,explicit
- Controlling non-flag arguments:
args
,argPos
- multi-mode programs:
modes
,auto
Supported Types: Each field in the record must be one of the supported
atomic types (String
, Int
, Integer
, Float
, Double
, Bool
, an
enumeration, a tuple of atomic types) or a list ([]
) or Maybe
wrapping
at atomic type.
Missing Fields: If a field is shared by multiple modes, it may be omitted in subsequent modes, and will default to the previous value.
Purity: Values created with annotations are not pure - the first time they are computed they will include the annotations, but subsequently they will not. If you wish to run the above example in a more robust way:
sample = cmdArgsMode
$ Sample{hello = ... -- as before
main = print =<< cmdArgsRun
sample
Even using this scheme, sometimes GHC's optimisations may share values who
have the same annotation. To disable sharing you may need to specify
{-# OPTIONS_GHC -fno-cse #-}
in the module you define the flags.
Pure annotations: Alternatively, you may use pure annotations, which are referentially transparent, but less type safe and more verbose. The initial example may be written as:
sample =
record
Sample{} [hello := def
+=
help
"World argument" +=
opt
"world"]
+=
summary
"Sample v1"
main = print =<< (cmdArgs_ sample :: IO Sample)
All the examples are written using impure annotations. To convert to pure annotations follow the rules:
Ctor {field1 = value1 &= ann1, field2 = value2} &= ann2 ==> record Ctor{} [field1 := value1 += ann1, field2 := value2] += ann2 Ctor (value1 &= ann1) value2 &= ann2 ==> record Ctor{} [atom value1 += ann1, atom value2] += ann2 modes [Ctor1{...}, Ctor2{...}] ==> modes_ [record Ctor1{} [...], record Ctor2{} [...]] Ctor {field1 = enum [X &= ann, Y]} ==> record Ctor{} [enum_ field1 [atom X += ann, atom Y]]
If you are willing to use TemplateHaskell, you can write in the impure syntax, but have your code automatically translated to the pure style. For more details see System.Console.CmdArgs.Quote.
- cmdArgs :: Data a => a -> IO a
- cmdArgsMode :: Data a => a -> Mode (CmdArgs a)
- cmdArgsRun :: Mode (CmdArgs a) -> IO a
- cmdArgs_ :: Data a => Annotate Ann -> IO a
- cmdArgsMode_ :: Data a => Annotate Ann -> Mode (CmdArgs a)
- cmdArgsApply :: CmdArgs a -> IO a
- data CmdArgs a = CmdArgs {
- cmdArgsValue :: a
- cmdArgsHelp :: Maybe String
- cmdArgsVersion :: Maybe String
- cmdArgsVerbosity :: Maybe Verbosity
- cmdArgsPrivate :: CmdArgsPrivate
- opt :: (Show a, Typeable a) => a -> Ann
- typ :: String -> Ann
- typFile :: Ann
- typDir :: Ann
- help :: String -> Ann
- name :: String -> Ann
- args :: Ann
- argPos :: Int -> Ann
- groupname :: String -> Ann
- details :: [String] -> Ann
- summary :: String -> Ann
- auto :: Ann
- program :: String -> Ann
- explicit :: Ann
- ignore :: Ann
- verbosity :: Ann
- helpArg :: [Ann] -> Ann
- versionArg :: [Ann] -> Ann
- verbosityArgs :: [Ann] -> [Ann] -> Ann
- noAtExpand :: Ann
- (&=) :: Data val => val -> Ann -> val
- modes :: Data val => [val] -> val
- enum :: Data val => [val] -> val
- (+=) :: Annotate ann -> ann -> Annotate ann
- record :: Data a => a -> [Annotate ann] -> Annotate ann
- atom :: Data val => val -> Annotate ann
- data Annotate ann = forall c f . (Data c, Data f) => (c -> f) := f
- enum_ :: (Data c, Data f) => (c -> f) -> [Annotate Ann] -> Annotate Ann
- modes_ :: [Annotate Ann] -> Annotate Ann
- module System.Console.CmdArgs.Verbosity
- module System.Console.CmdArgs.Default
- data Ann
- data Mode a
- class Typeable a => Data a
- class Typeable a
Running command lines
cmdArgs :: Data a => a -> IO aSource
Take impurely annotated records and run the corresponding command line.
Shortcut for
.
cmdArgsRun
. cmdArgsMode
To use cmdArgs
with custom command line arguments see
withArgs
.
cmdArgsMode :: Data a => a -> Mode (CmdArgs a)Source
Take impurely annotated records and turn them in to a Mode
value, that can
make use of the System.Console.CmdArgs.Explicit functions (i.e. process
).
Annotated records are impure, and will only contain annotations on their first use. The result of this function is pure, and can be reused.
cmdArgsRun :: Mode (CmdArgs a) -> IO aSource
Run a Mode structure. This function reads the command line arguments and then performs as follows:
- If invalid arguments are given, it will display the error message and exit.
- If
--help
is given, it will display the help message and exit. - If
--version
is given, it will display the version and exit. - In all other circumstances the program will return a value.
- Additionally, if either
--quiet
or--verbose
is given (seeverbosity
) it will set the verbosity (seesetVerbosity
).
cmdArgs_ :: Data a => Annotate Ann -> IO aSource
Take purely annotated records and run the corresponding command line.
Shortcut for
.
cmdArgsRun
. cmdArgsMode_
To use cmdArgs_
with custom command line arguments see
withArgs
.
cmdArgsMode_ :: Data a => Annotate Ann -> Mode (CmdArgs a)Source
Take purely annotated records and turn them in to a Mode
value, that can
make use of the System.Console.CmdArgs.Explicit functions (i.e. process
).
cmdArgsApply :: CmdArgs a -> IO aSource
Perform the necessary actions dictated by a CmdArgs
structure.
- If
cmdArgsHelp
isJust
, it will display the help message and exit. - If
cmdArgsVersion
isJust
, it will display the version and exit. - In all other circumstances it will return a value.
- Additionally, if
cmdArgsVerbosity
isJust
(seeverbosity
) it will set the verbosity (seesetVerbosity
).
A structure to store the additional data relating to --help
,
--version
, --quiet
and --verbose
.
CmdArgs | |
|
Constructing command lines
Attributes can work on a flag (inside a field), on a mode (outside the record),
or on all modes (outside the modes
call).
opt :: (Show a, Typeable a) => a -> AnnSource
Flag: "I want users to be able to omit the value associated with this flag."
Make the value of a flag optional. If --flag
is given, it will
be treated as --flag=this_argument
.
{hello = def &= opt "foo"} -h --hello[=VALUE] (default=foo)
Note that all flags in CmdArgs are optional, and if omitted will use their default value.
Those annotated with opt
also allow the flag to be present without an associated value.
As an example:
{hello = "DEFAULT" &= opt "OPTIONAL"}
$ main {hello = "DEFAULT"} $ main --hello {hello = "OPTIONAL"} $ main --hello=VALUE {hello = "VALUE"}
Flag/Mode: "The help message is ..."
Descriptive text used in the help output.
{hello = def &= help "Help message"} -h --hello=VALUE Help message
Flag: "Use this flag name for this field."
Add flags which trigger this option.
{hello = def &= name "foo"} -h --hello --foo=VALUE
Flag: "Put the nth non-flag argument here."
This field should be used to store a particular argument position (0-based).
{hello = def &= argPos 0}
groupname :: String -> AnnSource
Flag/Mode: "Give these flags/modes a group name in the help output."
This mode will be used for all following modes/flags, until the
next groupname
.
{hello = def &= groupname "Welcomes"} Welcomes -h --hello=VALUE
details :: [String] -> AnnSource
Mode: "A longer description of this mode is ..."
Suffix to be added to the help message.
Sample{..} &= details ["More details on the website www.example.org"]
summary :: String -> AnnSource
Modes: "My program name/version/copyright is ..."
One line summary of the entire program, the first line of
--help
and the only line of --version
. If the string contains a
version number component will also provide --numeric-version
.
Sample{..} &= summary "CmdArgs v0.0, (C) Neil Mitchell 1981"
Mode: "If the user doesn't give a mode, use this one."
This mode is the default. If no mode is specified and a mode has this attribute then that mode is selected, otherwise an error is raised.
modes [Mode1{..}, Mode2{..} &= auto, Mode3{..}]
program :: String -> AnnSource
Modes: "My program executable is named ..."
This is the name of the program executable. Only used in the help message. Defaults to the type of the mode.
Sample{..} &= program "sample"
Flag: "Don't guess any names for this field."
A field should not have any flag names guessed for it.
All flag names must be specified by flag
.
{hello = def &= explicit &= name "foo"} --foo=VALUE
Flag/Mode: "Ignore this field, don't let the user set it."
A mode or field is not dealt with by CmdArgs.
{hello = def, extra = def &= ignore} --hello=VALUE
versionArg :: [Ann] -> AnnSource
verbosityArgs :: [Ann] -> [Ann] -> AnnSource
Program: "Turn off @ expansion."
Usually arguments starting with @ are treated as a file containing a set of arguments. This annotation turns off that behaviour.
Sample{..} &= noAtExpand
Impure
(&=) :: Data val => val -> Ann -> valSource
Add an annotation to a value. Note that if the value is evaluated more than once the annotation will only be available the first time.
modes :: Data val => [val] -> valSource
Modes: "I want a program with multiple modes, like darcs or cabal."
Takes a list of modes, and creates a mode which includes them all.
If you want one of the modes to be chosen by default, see auto
.
data Modes = Mode1 | Mode2 | Mode3 deriving Data cmdArgs $ modes [Mode1,Mode2,Mode3]
enum :: Data val => [val] -> valSource
Flag: "I want several different flags to set this one field to different values."
This annotation takes a type which is an enumeration, and provides multiple separate flags to set the field to each value. The first element in the list is used as the value of the field.
data State = On | Off deriving Data data Mode = Mode {state :: State} cmdArgs $ Mode {state = enum [On &= help "Turn on",Off &= help "Turn off"]} --on Turn on --off Turn off
This annotation can be used to allow multiple flags within a field:
data Mode = Mode {state :: [State]} cmdArgs $ Mode {state = enum [[] &= ignore, [On] &= help "Turn on", [Off] &= help "Turn off"]}
Now --on --off
would produce Mode [On,Off]
.
Pure
record :: Data a => a -> [Annotate ann] -> Annotate annSource
Create a constructor/record. The first argument should be
the type of field, the second should be a list of fields constructed
originally defined by :=
or :=+
.
This operation is not type safe, and may raise an exception at runtime if any field has the wrong type or label.
This type represents an annotated value. The type of the underlying value is not specified.
enum_ :: (Data c, Data f) => (c -> f) -> [Annotate Ann] -> Annotate AnnSource
Like enum
, but using the pure annotations.
Re-exported for convenience
Provides a few opaque types (for writing type signatures),
verbosity control, default values with def
and the
Data
/Typeable
type classes.
The general type of annotations that can be associated with a value.
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
.
The Data
class comprehends a fundamental primitive gfoldl
for
folding over constructor applications, say terms. This primitive can
be instantiated in several ways to map over the immediate subterms
of a term; see the gmap
combinators later in this class. Indeed, a
generic programmer does not necessarily need to use the ingenious gfoldl
primitive but rather the intuitive gmap
combinators. The gfoldl
primitive is completed by means to query top-level constructors, to
turn constructor representations into proper terms, and to list all
possible datatype constructors. This completion allows us to serve
generic programming scenarios like read, show, equality, term generation.
The combinators gmapT
, gmapQ
, gmapM
, etc are all provided with
default definitions in terms of gfoldl
, leaving open the opportunity
to provide datatype-specific definitions.
(The inclusion of the gmap
combinators as members of class Data
allows the programmer or the compiler to derive specialised, and maybe
more efficient code per datatype. Note: gfoldl
is more higher-order
than the gmap
combinators. This is subject to ongoing benchmarking
experiments. It might turn out that the gmap
combinators will be
moved out of the class Data
.)
Conceptually, the definition of the gmap
combinators in terms of the
primitive gfoldl
requires the identification of the gfoldl
function
arguments. Technically, we also need to identify the type constructor
c
for the construction of the result type from the folded term type.
In the definition of gmapQ
x combinators, we use phantom type
constructors for the c
in the type of gfoldl
because the result type
of a query does not involve the (polymorphic) type of the term argument.
In the definition of gmapQl
we simply use the plain constant type
constructor because gfoldl
is left-associative anyway and so it is
readily suited to fold a left-associative binary operation over the
immediate subterms. In the definition of gmapQr, extra effort is
needed. We use a higher-order accumulation trick to mediate between
left-associative constructor application vs. right-associative binary
operation (e.g., (:)
). When the query is meant to compute a value
of type r
, then the result type withing generic folding is r -> r
.
So the result of folding is a function to which we finally pass the
right unit.
With the -XDeriveDataTypeable
option, GHC can generate instances of the
Data
class automatically. For example, given the declaration
data T a b = C1 a b | C2 deriving (Typeable, Data)
GHC will generate an instance that is equivalent to
instance (Data a, Data b) => Data (T a b) where gfoldl k z (C1 a b) = z C1 `k` a `k` b gfoldl k z C2 = z C2 gunfold k z c = case constrIndex c of 1 -> k (k (z C1)) 2 -> z C2 toConstr (C1 _ _) = con_C1 toConstr C2 = con_C2 dataTypeOf _ = ty_T con_C1 = mkConstr ty_T "C1" [] Prefix con_C2 = mkConstr ty_T "C2" [] Prefix ty_T = mkDataType "Module.T" [con_C1, con_C2]
This is suitable for datatypes that are exported transparently.
Data Bool | |
Data Char | |
Data Double | |
Data Float | |
Data Int | |
Data Int8 | |
Data Int16 | |
Data Int32 | |
Data Int64 | |
Data Integer | |
Data Ordering | |
Data Word | |
Data Word8 | |
Data Word16 | |
Data Word32 | |
Data Word64 | |
Data Exp | |
Data Match | |
Data Clause | |
Data Pat | |
Data Type | |
Data Dec | |
Data Name | |
Data FunDep | |
Data Pred | |
Data TyVarBndr | |
Data () | |
Data ModName | |
Data PkgName | |
Data OccName | |
Data NameFlavour | Although the NameFlavour type is abstract, the Data instance is not. The reason for this is that currently we use Data to serialize values in annotations, and in order for that to work for Template Haskell names introduced via the 'x syntax we need gunfold on NameFlavour to work. Bleh! The long term solution to this is to use the binary package for annotation serialization and then remove this instance. However, to do _that_ we need to wait on binary to become stable, since boot libraries cannot be upgraded seperately from GHC itself. This instance cannot be derived automatically due to bug #2701 |
Data NameSpace | |
Data Info | |
Data Fixity | |
Data FixityDirection | |
Data Lit | |
Data Body | |
Data Guard | |
Data Stmt | |
Data Range | |
Data FamFlavour | |
Data Foreign | |
Data Callconv | |
Data Safety | |
Data Pragma | |
Data Inline | |
Data RuleMatch | |
Data Phases | |
Data RuleBndr | |
Data Strict | |
Data Con | |
Data TyLit | |
Data LocalTime | |
Data ZonedTime | |
Data TimeOfDay | |
Data TimeZone | |
Data UTCTime | |
Data NominalDiffTime | |
Data Day | |
Data Ann | |
Data Verbosity | |
Data a => Data [a] | |
(Data a, Integral a) => Data (Ratio a) | |
Typeable a => Data (Ptr a) | |
Typeable a => Data (ForeignPtr a) | |
Data a => Data (Maybe a) | |
Data a => Data (CmdArgs a) | |
(Data a, Data b) => Data (Either a b) | |
(Data a, Data b) => Data (a, b) | |
(Typeable a, Data b, Ix a) => Data (Array a b) | |
(Data a, Data b, Data c) => Data (a, b, c) | |
(Data a, Data b, Data c, Data d) => Data (a, b, c, d) | |
(Data a, Data b, Data c, Data d, Data e) => Data (a, b, c, d, e) | |
(Data a, Data b, Data c, Data d, Data e, Data f) => Data (a, b, c, d, e, f) | |
(Data a, Data b, Data c, Data d, Data e, Data f, Data g) => Data (a, b, c, d, e, f, g) |
class Typeable a
The class Typeable
allows a concrete representation of a type to
be calculated.