cmdargs-0.1: Command line argument processing

System.Console.CmdArgs

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 = mode $ Sample{hello = def &= text "World argument" & empty "world"}
main = print =<< cmdArgs "Sample v1, (C) Neil Mitchell 2009" [sample]

Attributes are used to control a number of behaviours:

Synopsis

Running command lines

cmdArgsSource

Arguments

:: Data a 
=> String

Information about the program, something like: "ProgramName v1.0, Copyright PersonName 2000".

-> [Mode a]

The modes of operation, constructed by mode. For single mode programs it is a singleton list.

-> IO a 

The main entry point for programs using CmdArgs. For an example see System.Console.CmdArgs.

modeValue :: Mode a -> aSource

Extract the default value from inside a Mode.

Attributes

Attribute mechanism

mode :: Data a => a -> Mode aSource

Construct a Mode from a value annotated with attributes.

data Mode a Source

Instances

Show a => Show (Mode a) 

(&=) :: a -> Attrib -> aSource

Add attributes to a value. Always returns the first argument, but has a non-pure effect on the environment. Take care when performing program transformations.

 value &= attrib1 & attrib2

(&) :: Attrib -> Attrib -> AttribSource

Combine two attributes.

data Attrib Source

Attributes to modify the behaviour.

Flag attributes

text :: String -> AttribSource

Flag/Mode: Descriptive text used in the help output.

 {str = def &= text "Help message"}
   -s --str=VALUE      Help message

typ :: String -> AttribSource

Flag: The the type of a flag's value, usually upper case. Only used for the help message.

 {str = def &= typ "FOO"}
   -s --str=FOO

typFile :: AttribSource

Flag: Alias for typ "FILE".

typDir :: AttribSource

Flag: Alias for typ "DIR".

empty :: (Show a, Typeable a) => a -> AttribSource

Flag: Make the value of a flag optional, using the supplied value if none is given.

 {str = def &= empty "foo"}
   -s --str[=VALUE]    (default=foo)

flag :: String -> AttribSource

Flag: Add flags which trigger this option.

 {str = def &= flag "foo"}
   -s --str --foo=VALUE

explicit :: AttribSource

Flag: A field should not have any flag names guessed for it. All flag names must be specified by flag.

 {str = def &= explicit & flag "foo"}
   --foo=VALUE

enum :: (Typeable a, Eq a, Show a) => a -> [a] -> aSource

Flag: A field is an enumeration of possible values.

 data Choice = Yes | No deriving (Data,Typeable,Show,Eq)
 data Sample = Sample {choice :: Choice}
 {choice = Yes & enum [Yes &= "say yes", No &= "say no"]}
   -y --yes    say yes (default)
   -n --no     say no

args :: AttribSource

Flag: This field should be used to store the non-flag arguments. Can only be applied to fields of type [String].

 {strs = def &= args}

argPos :: Int -> AttribSource

Flag: This field should be used to store a particular argument position (0-based). Can only be applied to fields of type String.

 {str = def &= argPos 0}

unknownFlags :: AttribSource

Flag: This field should be used to store all unknown flag arguments. If no unknownFlags field is set, unknown flags raise errors. Can only be applied to fields of type [String].

 {strs = def &= unknownFlags}

Mode attributes

prog :: String -> AttribSource

Mode: This is the name of the program running, used to override the result from getProgName. Only used in the help message.

helpSuffix :: [String] -> AttribSource

Mode: Suffix to be added to the help message.

defMode :: AttribSource

Mode: 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.

Verbosity control

isQuiet :: IO BoolSource

Used to test if essential messages should be output to the user. Always true (since even --quiet wants essential messages output). Must be called after cmdArgs.

isNormal :: IO BoolSource

Used to test if normal messages should be output to the user. True unless --quiet is specified. Must be called after cmdArgs.

isLoud :: IO BoolSource

Used to test if helpful debug messages should be output to the user. False unless --verbose is specified. Must be called after cmdArgs.

Display help information

data HelpFormat Source

Format to display help in.

Constructors

Text

As output on the console.

HTML

Suitable for inclusion in web pages (uses a table rather than explicit wrapping).

cmdArgsHelp :: String -> [Mode a] -> HelpFormat -> IO StringSource

Display the help message, as it would appear with --help. The first argument should match the first argument to cmdArgs.

Default values

class Default a whereSource

Class for default values

Methods

def :: aSource

Provide a default value

Re-exported for convenience

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