cmdargs

System.Console.CmdArgs.Implicit

Contents

Description

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:

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
 many [Ctor1{...}, Ctor2{...}] ==> many_ [record Ctor1{} [...], record Ctor2{} [...]]
 Ctor {field1 = enum [X &= ann, Y]} ==> record Ctor{} [field1 := enum_ [atom X += ann, atom Y]]

Synopsis

Running command lines

cmdArgs :: Data a => a -> IO a

Take impurely annotated records and run the corresponding command line. Shortcut for cmdArgsRun . cmdArgsMode.

To use cmdArgs with custom command line arguments see System.Environment.withArgs.

cmdArgsMode :: Data a => a -> Mode (CmdArgs a)

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 a

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 (see verbosity) it will set the verbosity (see setVerbosity).

cmdArgs_ :: Data a => Annotate Ann -> IO a

Take purely annotated records and run the corresponding command line. Shortcut for cmdArgsRun . cmdArgsMode_.

To use cmdArgs_ with custom command line arguments see System.Environment.withArgs.

cmdArgsMode_ :: Data a => Annotate Ann -> Mode (CmdArgs a)

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 a

Perform the necessary actions dictated by a CmdArgs structure.

data CmdArgs a

A structure to store the additional data relating to --help, --version, --quiet and --verbose.

Constructors

CmdArgs 

Fields

cmdArgsValue :: a

The underlying value being wrapped.

cmdArgsHelp :: Maybe String

Just if --help is given, then gives the help message for display, including a trailing newline.

cmdArgsVersion :: Maybe String

Just if --version is given, then gives the version message for display, including a trailing newline.

cmdArgsVerbosity :: Maybe Verbosity

Just if --quiet or --verbose is given, then gives the verbosity to use.

cmdArgsPrivate :: CmdArgsPrivate

Private: Only exported due to Haddock limitations.

Instances

Functor CmdArgs 
Typeable1 CmdArgs 
Eq a => Eq (CmdArgs a) 
Data a => Data (CmdArgs a) 
Ord a => Ord (CmdArgs a) 
Show a => Show (CmdArgs a) 

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

Impure

(&=) :: Data val => val -> Ann -> val

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

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

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.

 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

Pure

(+=) :: Annotate ann -> ann -> Annotate ann

Add an annotation to a value.

record :: Data a => a -> [Annotate b] -> Annotate b

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.

atom :: Data val => val -> Annotate ann

Lift a pure value to an annotation.

data Annotate ann

This type represents an annotated value. The type of the underlying value is not specified.

Constructors

forall c f . (Data c, Data f) => (c -> f) := f

Construct a field, fieldname := value.

enum_ :: (Data c, Data f) => (c -> f) -> [Annotate Ann] -> Annotate Ann

Like enum, but using the pure annotations.

modes_ :: [Annotate Ann] -> Annotate Ann

Like modes, 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.

data Ann

The general type of annotations that can be associated with a value.

Instances

data Mode a

A mode. Each mode has three main features:

Instances

class Typeable a => Data a

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

Instances

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 () 
Data Ann 
Data Verbosity 
Data CmdArgsPrivate 
Data Flag 
Data Test16 
Data MyInt 
Data Test15 
Data Test14 
Data Test13 
Data Test12 
Data Test11 
Data Test10 
Data Test9 
Data XYZ 
Data Test8 
Data Test7 
Data Test6 
Data Test5 
Data ABC 
Data Test4 
Data Test3 
Data Test2 
Data Test1 
Data Maker 
Data Method 
Data HLint 
Data Diffy 
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)