cmdlib-0.3.5: a library for command line parsing & online help

System.Console.CmdLib

Contents

Description

A library for setting up a commandline parser and help generator for an application. It aims for conciseness, flexibility and composability. It supports both non-modal and modal (with subcommands -- like darcs, cabal and the like) applications.

The library supports two main styles of representing flags and commands. These are called Record and ADT, respectively, by the library. The Record representation is more straightforward and easier to use in most instances. The ADT interface is suitable for applications that require exact correspondence between the commandline and its runtime representation, or when an existing application is being ported to cmdlib that is using this style to represent flags.

Using the Record-based interface, a simple Hello World application could look like this:

 {-# LANGUAGE FlexibleInstances, MultiParamTypeClasses, DeriveDataTypeable #-}
 import System.Console.CmdLib
 import Control.Monad

 data Main = Main { greeting :: String, again :: Bool }
     deriving (Typeable, Data, Eq)

 instance Attributes Main where
     attributes _ = group "Options" [
         greeting %> [ Help "The text of the greeting.", ArgHelp "TEXT"
                     , Default "Hello world!" ],
         again    %> Help "Say hello twice." ]

 instance RecordCommand Main where
     mode_summary _ = "Hello world with argument parsing."

 main = getArgs >>= executeR Main {} >>= \opts -> do
   putStrLn (greeting opts)

Then, saying ./hello --help will give us:

 Hello world with argument parsing.

 Options:
     --greeting=TEXT   The text of the greeting. (default: Hello world!)
     --again[=yes|no]  Say hello twice. (default: no)

Synopsis

News

Since version 0.3.3: Added recordCommand, making it possible to set defaultCommand also for record-based command sets (and in general, use any API that expects a single Command).

| Since version 0.3.2: Added a new Required attribute for mandatory flags/arguments to be used in record-based commands. Also added automatic synopsis derivation for record-based commands, which includes all flags and options. Flag values are evaluated during parsing now, providing early error reporting. Unambiguous command prefixes are now accepted.

| Since version 0.3.1: rec_optionStyle and rec_superCommand have been added to the RecordCommand class, granting more flexibility to the record-based command interface.

| Since version 0.3: dispatchR no longer takes a cmd argument, as it was never used for anything and was simply confusing. A new function, dispatchOr has been added to allow the program to continue despite otherwise fatal errors (unknown command, unknown flags). New function, commandNames, has been added, to go from [CommandWrap] to [String]. The CommandWrap type is now exported (opaque). The RecordCommand class now has a mode_help method. RecordMode is no longer exported.

| Since version 0.2: The Positional arguments are no longer required to be strings. A default (fallback) command may be provided to dispatch/dispatchR (this has also incompatibly changed their signature, sorry about that! I have tried to make this extensible though...). The help command can now be disabled (dispatch [noHelp] ...). Commands can now specify how to process options: permuted, non-permuted or no options at all. See optionStyle.

Attributes

To each flag, a number of attributes can be attached. Many reasonable defaults are provided by the library. The attributes are described by the Attribute type and are attached to flags using %> and the related operators (all described in this section).

data Attribute Source

Constructors

Short [Char]

Set a list of short flags (single character per flag, like in -c, -h) for an option. Without the leading -.

Long [String]

Set a list of long flags for an option.

InvLong [String]

Set a list of long flags for an inversion of the option. Only used for boolean invertible options. See also long.

Invertible Bool

Whether this option is invertible. Only applies to boolean options and defaults to True. (Invertible means that for --foo, there are --no-foo and --foo=no alternatives. A non-invertible option will only create --foo.)

Help String

Set help string (one-line summary) for an option. Displayed in help.

Extra Bool

When True, this option will contain the list of non-option arguments passed to the command. Only applicable to [String]-typed options. Options marked extra will not show up in help and neither will they be recognized by their name on commandline.

Positional Int

When set, this option will not show up on help and won't create a flag (similar to Extra), but instead it will contain the n-th non-option argument. The argument used up by such a positional option will not show up in the list of non-option arguments.

Required Bool

When True, this option will require that the argument must be provided. If the argument is also Positional, any preceeding Positional arguments should also be Required.

ArgHelp String

Set the help string for an argument, the FOO in --wibblify=FOO.

forall a . Data a => Default a

Set default value for this option. The default is only applied when its type matches the option's parameter type, otherwise it is ignored.

forall a . Data a => Global (a -> IO ())

When this attribute is given, the flag's value will be passed to the provided IO action (which would presumably record the flag's value in a global IORef for later use). Like with Default, the attribute is only effective if the parameter type of the provided function matches the parameter type of the option to which the attribute is applied.

Enabled Bool

Whether the option is enabled. Disabled options are not recognized and are not shown in help (effectively, they do not exist). Used to enable a subset of all available options for a given command. For Record-based commands (see RecordCommand), this is handled automatically based on fields available in the command's constructor. Otherwise, constructs like

 enable <% option1 +% option2 +% option3 %% disable <% option4

may be quite useful.

Group String

Set the group name for this option. The groups are used to section the help output (the options of a given group are shown together, under the heading of the group). The ordering of the groups is given by the first flag of each group. Flags themselves are in the order in which they are given in the ADT or Record in question.

Instances

Show Attribute 
AttributeList Attribute 
Eq k => AttributeMapLike k [(k, [Attribute])] 
Eq k => AttributeMapLike k (k -> [Attribute]) 
AttributeList [Attribute] 

enable :: AttributeSource

For convenience. Same as Enabled True.

disable :: AttributeSource

For convenience. Same as Enabled False.

long :: String -> [Attribute]Source

For convenience. Same as Long [foo] %+ InvLong [no-foo]

short :: Char -> AttributeSource

For convenience. Same as Short [x]

(%%) :: (AttributeMapLike k a, AttributeMapLike k b) => a -> b -> AttributeMap kSource

Join attribute mappings. E.g. Key1 %> Attr1 %+ Attr2 %% Key2 %> Attr3 %+ Attr4. Also possible is [ Key1 %> Attr1, Key2 %> Attr2 ] %% Key3 %> Attr3, or many other variations.

(%>) :: (ToKey k, AttributeList attr) => k -> attr -> AttributeMap KeySource

Attach a (list of) attributes to a key. The key is usually either an ADT constructor (for use with ADTFlag-style flags) or a record selector (for use with RecordFlags).

 data RFlags = Flags { wibblify :: Int, simplify :: Bool }
 data AFlag = Simplify | Wibblify Int
 rattr = wibblify %> Help "Add a wibblification pass." (%% ...)
 aattr = Wibblify %> Help "Add a wibblification pass." (%% ...)

%+ can be used to chain multiple attributes:

 attrs = wibblify %> Help "some help" %+ Default (3 :: Int) %+ ArgHelp "intensity"

But lists work just as fine:

 attrs = wibblify %> [ Help "some help", Default (3 :: Int), ArgHelp "intensity" ]

(<%) :: forall keys. Keys keys => Attribute -> keys -> AttributeMap KeySource

Attach an attribute to multiple keys: written from right to left, i.e. Attribute <% Key1 +% Key2. Useful for setting up option groups (although using group may be more convenient in this case) and option enablement.

(%+) :: (AttributeList a, AttributeList b) => a -> b -> [Attribute]Source

Join multiple attributes into a list. Available for convenience (using [Attribute] directly works just as well if preferred, although this is not the case with keys, see +%).

(+%) :: forall a b. (Keys a, Keys b) => a -> b -> [Key]Source

Join multiple keys into a list, e.g. Key1 +% Key2. Useful with <% to list multiple (possibly heterogenously-typed) keys.

everywhere :: Eq k => Attribute -> AttributeMap kSource

Set an attribute on all keys.

group :: forall k a. AttributeMapLike k a => String -> a -> AttributeMap kSource

Create a group. This extracts all the keys that are (explicitly) mentioned in the body of the group and assigns the corresponding Group attribute to them. Normally used like this:

 group "Group name" [ option %> Help "some help"
                    , another %> Help "some other help" ]

Do not let the type confuse you too much. :)

Flags

Flags (commandline options) can be represented in two basic styles, either as a plain ADT (algebraic data type) or as a record type. These two styles are implemented using the ADT wrapper for the former and and a Record wrapper for the latter. You need to make your type an instance of the Attributes class, which can be used to attach attributes to the flags.

data Attributes adt => ADT adt Source

The ADT wrapper type allows use of classic ADTs (algebraic data types) for flag representation. The flags are then passed to the command as a list of values of this type. However, you need to make the type an instance of the Attributes first (if you do not wish to attach any attributes, you may keep the instance body empty). E.g.:

 data Flag = Simplify | Wibblify Int
 instance Attributes where
     attributes _ = Wibblify %> Help "Add a wibblification pass." %+ ArgHelp "intensity" %%
                    Simplify %> Help "Enable a two-pass simplifier."

The Command instances should then use (ADT Flag) for their second type parameter (the flag type).

Instances

Eq adt => Eq (ADT adt) 
(Eq (ADT adt), Attributes adt, Data adt) => FlagType (ADT adt) 

data Attributes rec => Record rec Source

This wrapper type allows use of record types (single or multi-constructor) for handling flags. Each field of the record is made into a single flag of the corresponding type. The record needs to be made an instance of the Attributes class. That way, attributes can be attached to the field selectors, although when used with RecordCommand, its rec_options method can be used as well and the Attributes instance left empty.

 data Flags = Flags { wibblify :: Int, simplify :: Bool }
 instance Attributes Flags where
     attributes _ =
        wibblify %> Help "Add a wibblification pass." %+ ArgHelp "intensity" %%
        simplify %> Help "Enable a two-pass simplifier."

A single value of the Flags type will then be passed to the Command instances (those that use Record Flags as their second type parameter), containing the value of the rightmost occurence for each of the flags.

TODO: List-based option types should be accumulated instead of overriden.

Instances

(Eq rec, Attributes rec) => Eq (Record rec) 
(Eq rec, Eq (Record rec), Data rec, Attributes rec) => FlagType (Record rec) 
(Eq cmd, Eq (Record cmd), RecordCommand cmd, Data cmd, Attributes cmd) => Command (RecordMode cmd) (Record cmd) 

class Attributes a whereSource

Methods

attributes :: a -> AttributeMap KeySource

readFlag :: Data b => a -> String -> bSource

noAttributes :: AttributeMap kSource

Commands

(%:) :: (Commands a, Commands b) => a -> b -> [CommandWrap]Source

Chain commands into a list suitable for dispatch and helpCommands. E.g.:

 dispatch (Command1 %: Command2 %: Command3) opts

commandGroup :: Commands a => String -> a -> [CommandWrap]Source

class (Typeable cmd, FlagType flag) => Command cmd flag | cmd -> flag whereSource

A class that describes a single (sub)command. The cmd type parameter is just for dispatch (and the default command name is derived from this type's name, but this can be overriden). It could be an empty data decl as far as this library is concerned, although you may choose to store information in it.

To parse the commandline for a given command, see execute. The basic usage can look something like this:

 data Flag = Summary | Unified Bool | LookForAdds Bool
 instance ADTFlag Flag

 [...]

 data Whatsnew = Whatsnew deriving Typeable

 instance Command Whatsnew (ADT Flag) where
  options _ =  enable <% Summary +% Unified +% LookForAdds
  summary _ = "Create a patch from unrecorded changes."

  run _ f opts = do putStrLn $ "Record."
                    putStrLn $ "Options: " ++ show f
                    putStrLn $ "Non-options: " ++ show opts

Methods

options :: cmd -> AttributeMap KeySource

An Attribute mapping for flags provided by the flag type parameter.

supercommand :: cmd -> BoolSource

Set this to True if the command is a supercommand (i.e. expects another subcommand). Defaults to False. Supercommands can come with their own options, which need to appear between the supercommand and its subcommand. Any later options go to the subcommand. The run (and description) method of a supercommand should use dispatch and helpCommands respectively (on its list of subcommands) itself.

optionStyle :: cmd -> OptionStyleSource

How to process options for this command. NoOptions disables option processing completely and all arguments are passed in the [String] parameter to run. Permuted collects everything that looks like an option (starts with a dash) and processes it. The non-option arguments are filtered and passed to run like above. Finally, NonPermuted only processes options until a first non-option argument is encountered. The remaining arguments are passed unchanged to run.

run :: cmd -> Folded flag -> [String] -> IO ()Source

The handler that actually runs the command. Gets the setup value as folded from the processed options (see Combine) and a list of non-option arguments.

synopsis :: cmd -> StringSource

Provides the commands' short synopsis.

summary :: cmd -> StringSource

Provides a short (one-line) description of the command. Used in help output.

help :: cmd -> StringSource

cmdname :: cmd -> StringSource

The name of the command. Normally derived automatically from cmd, but may be overriden.

cmd :: cmdSource

A convenience undefined of the command, for use with Commands.

cmd_flag_defaults :: cmd -> (flag -> [Attribute]) -> Folded flagSource

Instances

Command HelpCommand () 
(Eq cmd, Eq (Record cmd), RecordCommand cmd, Data cmd, Attributes cmd) => Command (RecordMode cmd) (Record cmd) 

dispatch :: [DispatchOpt] -> [CommandWrap] -> [String] -> IO ()Source

Given a list of commands (see %:) and a list of commandline arguments, dispatch on the command name, parse the commandline options (see execute) and transfer control to the command. This function also implements the help pseudocommand.

dispatchOrSource

Arguments

:: (String -> IO ())

eg. die

-> [DispatchOpt] 
-> [CommandWrap] 
-> [String] 
-> IO () 

Like dispatch but with the ability to control what happens when there is an error on user input

execute :: forall cmd f. Command cmd f => cmd -> [String] -> IO ()Source

Parse options for and execute a single command (see Command). May be useful for programs that do not need command-based dispatch, but still make use of the Command class to describe themselves. Handles --help internally. You can use this as the entrypoint if your application is non-modal (i.e. it has no subcommands).

helpOptions :: forall cmd f. Command cmd f => cmd -> StringSource

noHelp :: DispatchOptSource

defaultCommand :: (Command f x, Typeable (Folded x)) => f -> DispatchOptSource

data OptionStyle Source

How to process options for a command. See optionStyle for details.

Instances

data CommandWrap Source

Instances

Commands CommandWrap 
Commands [CommandWrap] 

commandNamesSource

Arguments

:: Bool

show hidden commands too

-> [CommandWrap] 
-> [String] 

This could be used to implement a disambiguation function

Note that there isn't presently a notion of hidden commands, but we're taking them into account now for future API stability

Record-based commands

class Data cmd => RecordCommand cmd whereSource

A bridge that allows multi-constructor record types to be used as a description of a command set. In such a type, each constructor corresponds to a single command and its fields to its options. To describe a program with two commands, foo and bar, each taking a --wibble boolean option and bar also taking a --text=string option, you can write:

 data Commands = Foo { wibble :: Bool }
               | Bar { wibble :: Bool, text :: String }

 instance RecordCommand Commands where (...)

You should at least implement run', rec_options and mode_summary are optional.

Methods

run' :: cmd -> [String] -> IO ()Source

run' is your entrypoint into the whole set of commands. You can dispatch on the command by looking at the constructor in cmd:

 run' cmd@(Foo {}) _ = putStrLn $ "Foo running. Wibble = " ++ show (wibble cmd)
 run' cmd@(Bar {}) _ = putStrLn "This is bar."

rec_options :: cmd -> AttributeMap KeySource

You can also provide extra per-command flag attributes (match on the constructor like with run'). The attributes shared by various commands can be set in rec_attrs in Attributes instead.

rec_optionStyle :: cmd -> OptionStyleSource

Set the per-command option style, useful for supercommands to pass their options through to another dispatch, by using NoOptions.

rec_superCommand :: cmd -> BoolSource

Pattern match like in run' to identify any supercommands, which will allow --help flags to be passed through to the sub-commands.

mode_summary :: cmd -> StringSource

Provide a summary help string for each mode. Used in help output. Again, pattern match like in run'.

mode_help :: cmd -> StringSource

Provide a help blurb for each mode. Use patterns like in run'.

mode_synopsis :: cmd -> Maybe StringSource

Optionally override the default usage string for each mode. Use patterns like in run'.

recordCommands :: forall cmd. (Eq cmd, Eq (Record cmd), Data cmd, RecordCommand cmd, Attributes cmd) => cmd -> [CommandWrap]Source

Construct a command list (for dispatch/helpCommands) from a multi-constructor record data type. See also RecordCommand. Alternatively, you can use dispatchR directly.

dispatchR :: forall cmd f. (Eq cmd, Eq (Record cmd), Attributes cmd, RecordCommand cmd, Command (RecordMode cmd) f, Folded f ~ cmd) => [DispatchOpt] -> [String] -> IO cmdSource

A command parsing & dispatch entry point for record-based commands. Ex. (see RecordCommand):

 main = getArgs >>= dispatchR [] >>= \x -> case x of
   Foo {} -> putStrLn $ "You asked for foo. Wibble = " ++ show (wibble x)
   Bar {} -> putStrLn $ "You asked for bar. ..."

executeR :: forall cmd. (Eq cmd, Eq (Record cmd), Attributes cmd, RecordCommand cmd) => cmd -> [String] -> IO cmdSource

Like execute, but you get the flags as a return value. This is useful to implement non-modal applications with record-based flags, eg.:

 data Main = Main { greeting :: String, again :: Bool }
     deriving (Typeable, Data, Eq)
 instance Attributes Main where -- (...)
 instance RecordCommand Main
 main = getArgs >>= executeR Main {} >>= \opts -> do
    putStrLn (greeting opts) -- (...)

recordCommand :: forall cmd. (Eq cmd, Eq (Record cmd), Data cmd, RecordCommand cmd, Attributes cmd) => cmd -> RecordMode cmdSource

Obtain a value that is an instance of Command, i.e. suitable for use with defaultCommand and other Command-based APIs.

Utilities

globalFlag :: Typeable a => a -> (a -> IO (), IO a)Source

Use noAttributes specify an empty attribute set. Available since 0.3.2.

Create a global setter/getter pair for a flag. The setter can be then passed to the Global attribute and the getter used globally to query value of that flag. Example:

 data Flag = Wibblify Int | Verbose Bool
 (setVerbose, isVerbose) = globalFlag False

 instance Attributes Flag where
     attributes _ = Verbose %> Global setVerbose

 putVerbose str = isVerbose >>= flip when (putStrLn str)

readCommon :: Data a => String -> aSource

The default parser for option arguments. Handles strings, string lists (always produces single-element list), integers, booleans (yes|true|1 vs no|false|0), PathF and integer lists (--foo=1,2,3).

(<+<) :: (Typeable a, Typeable b, Monad m) => m a -> m b -> m aSource

die :: String -> IO aSource

Helper for dying with an error message (nicely, at least compared to fail in IO).

Convenience re-exports

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

getArgs :: IO [String]

Computation getArgs returns a list of the program's command line arguments (not including the program name).