options-1.0: A powerful and easy-to-use command-line option parser.

Safe HaskellSafe-Inferred

Options

Contents

Description

The options package lets library and application developers easily work with command-line options.

The following example is a full program that can accept two options, --message and --quiet:

import Control.Applicative
import Options

data MainOptions = MainOptions
    { optMessage :: String
    , optQuiet :: Bool
    }

instance Options MainOptions where
    defineOptions = pure MainOptions
        <*> simpleOption "message" "Hello world!"
            "A message to show the user."
        <*> simpleOption "quiet" False
            "Whether to be quiet."

main :: IO ()
main = runCommand $ \opts args -> do
    if optQuiet opts
        then return ()
        else putStrLn (optMessage opts)
$ ./hello
Hello world!
$ ./hello --message='ciao mondo'
ciao mondo
$ ./hello --quiet
$

In addition, this library will automatically create documentation options such as --help and --help-all:

$ ./hello --help
Help Options:
  -h, --help
    Show option summary.
  --help-all
    Show all help options.

Application Options:
  --message :: text
    A message to show the user.
    default: "Hello world!"
  --quiet :: bool
    Whether to be quiet.
    default: false

Synopsis

Defining options

class Options opts whereSource

Options are defined together in a single data type, which will be an instance of Options.

See defineOptions for details on defining instances of Options.

Methods

defineOptions :: DefineOptions optsSource

Defines the structure and metadata of the options in this type, including their types, flag names, and documentation.

Options with a basic type and a single flag name may be defined with simpleOption. Options with more complex requirements may be defined with defineOption.

Non-option fields in the type may be set using applicative functions such as pure.

Options may be included from another type by using a nested call to defineOptions.

Library authors are encouraged to aggregate their options into a few top-level types, so application authors can include it easily in their own option definitions.

defaultOptions :: Options opts => optsSource

An options value containing only the default values for each option. This is equivalent to the options value when parsing an empty argument list.

simpleOption :: SimpleOptionType a => String -> a -> String -> DefineOptions aSource

Defines a new option in the current options type.

Defining subcommands

data Subcommand cmdOpts action Source

subcommandSource

Arguments

:: (Options cmdOpts, Options subcmdOpts) 
=> String

The subcommand name.

-> (cmdOpts -> subcmdOpts -> [String] -> action)

The action to run.

-> Subcommand cmdOpts action 

Running main with options

runCommand :: (MonadIO m, Options opts) => (opts -> [String] -> m a) -> m aSource

Retrieve getArgs, and attempt to parse it into a valid value of an Options type plus a list of left-over arguments. The options and arguments are then passed to the provided computation.

If parsing fails, this computation will print an error and call exitFailure.

If parsing succeeds, and the user has passed a --help flag, and the developer is using the default help flag definitions, then this computation will print documentation and call exitSuccess.

See runSubcommand for details on subcommand support.

runSubcommand :: (Options opts, MonadIO m) => [Subcommand opts (m a)] -> m aSource

Used to run applications that are split into subcommands.

Use subcommand to define available commands and their actions, then pass them to this computation to select one and run it. If the user specifies an invalid subcommand, this computation will print an error and call exitFailure. In handling of invalid flags or --help, runSubcommand acts like runCommand.

import Control.Applicative
import Control.Monad (unless)
import Options

data MainOptions = MainOptions { optQuiet :: Bool }
instance Options MainOptions where
    defineOptions = pure MainOptions
        <*> simpleOption "quiet" False "Whether to be quiet."

data HelloOpts = HelloOpts { optHello :: String }
instance Options HelloOpts where
    defineOptions = pure HelloOpts
        <*> simpleOption "hello" "Hello!" "How to say hello."

data ByeOpts = ByeOpts { optName :: String }
instance Options ByeOpts where
    defineOptions = pure ByeOpts
        <*> simpleOption "name" "" "The user's name."

hello :: MainOptions -> HelloOpts -> [String] -> IO ()
hello mainOpts opts args = unless (optQuiet mainOpts) $ do
    putStrLn (optHello opts)

bye :: MainOptions -> ByeOpts -> [String] -> IO ()
bye mainOpts opts args = unless (optQuiet mainOpts) $ do
    putStrLn ("Good bye " ++ optName opts)

main :: IO ()
main = runSubcommand
    [ subcommand "hello" hello
    , subcommand "bye" bye
    ]
$ ./app hello
Hello!
$ ./app hello --hello='Allo!'
Allo!
$ ./app bye
Good bye 
$ ./app bye --name='Alice'
Good bye Alice

Parsing argument lists

parsedError :: Parsed a => a -> Maybe StringSource

Get the error that prevented options from being parsed from argv, or Nothing if no error was detected.

parsedHelp :: Parsed a => a -> StringSource

Get a help message to show the user. If the arguments included a help flag, this will be a message appropriate to that flag. Otherwise, it is a summary (equivalent to --help).

This is always a non-empty string, regardless of whether the parse succeeded or failed. If you need to perform additional validation on the options value, this message can be displayed if validation fails.

Parsing options

parsedOptions :: ParsedOptions opts -> Maybe optsSource

Get the options value that was parsed from argv, or Nothing if the arguments could not be converted into options.

Note: This function return Nothing if the user provided a help flag. To check whether an error occured during parsing, check the value of parsedError.

parsedArguments :: ParsedOptions opts -> [String]Source

Get command-line arguments remaining after parsing options. The arguments are unchanged from the original argument list, and have not been decoded or otherwise transformed.

parseOptions :: Options opts => [String] -> ParsedOptions optsSource

Attempt to convert a list of command-line arguments into an options value. This can be used by application developers who want finer control over error handling, or who want to perform additional validation on the options value.

The argument list must be in the same encoding as the result of getArgs.

Use parsedOptions, parsedArguments, parsedError, and parsedHelp to inspect the result of parseOptions.

Example:

getOptionsOrDie :: Options a => IO a
getOptionsOrDie = do
    argv <- System.Environment.getArgs
    let parsed = parseOptions argv
    case parsedOptions parsed of
        Just opts -> return opts
        Nothing -> case parsedError parsed of
            Just err -> do
                hPutStrLn stderr (parsedHelp parsed)
                hPutStrLn stderr err
                exitFailure
            Nothing -> do
                hPutStr stdout (parsedHelp parsed)
                exitSuccess

Parsing sub-commands

parsedSubcommand :: ParsedSubcommand action -> Maybe actionSource

Get the subcommand action that was parsed from argv, or Nothing if the arguments could not be converted into a valid action.

Note: This function return Nothing if the user provided a help flag. To check whether an error occured during parsing, check the value of parsedError.

parseSubcommand :: Options cmdOpts => [Subcommand cmdOpts action] -> [String] -> ParsedSubcommand actionSource

Attempt to convert a list of command-line arguments into a subcommand action. This can be used by application developers who want finer control over error handling, or who want subcommands that run in an unusual monad.

The argument list must be in the same encoding as the result of getArgs.

Use parsedSubcommand, parsedError, and parsedHelp to inspect the result of parseSubcommand.

Example:

runSubcommand :: Options cmdOpts => [Subcommand cmdOpts (IO a)] -> IO a
runSubcommand subcommands = do
    argv <- System.Environment.getArgs
    let parsed = parseSubcommand subcommands argv
    case parsedSubcommand parsed of
        Just cmd -> cmd
        Nothing -> case parsedError parsed of
            Just err -> do
                hPutStrLn stderr (parsedHelp parsed)
                hPutStrLn stderr err
                exitFailure
            Nothing -> do
                hPutStr stdout (parsedHelp parsed)
                exitSuccess

Advanced option definitions

data OptionType val Source

An option's type determines how the option will be parsed, and which Haskell type the parsed value will be stored as. There are many types available, covering most basic types and a few more advanced types.

defineOption :: OptionType a -> (Option a -> Option a) -> DefineOptions aSource

Defines a new option in the current options type.

All options must have one or more flags. Options may also have a default value, a description, and a group.

The flags are how the user specifies an option on the command line. Flags may be short or long. See optionShortFlags and optionLongFlags for details.

defineOption optionType_word16 (\o -> o
    { optionLongFlags = ["port"]
    , optionDefault = 80
    })

data Option a Source

optionShortFlags :: Option a -> [Char]Source

Short flags are a single character. When entered by a user, they are preceded by a dash and possibly other short flags.

Short flags must be a letter or a number.

Example: An option with optionShortFlags = ['p'] may be set using:

$ ./app -p 443
$ ./app -p443

optionLongFlags :: Option a -> [String]Source

Long flags are multiple characters. When entered by a user, they are preceded by two dashes.

Long flags may contain letters, numbers, '-', and '_'.

Example: An option with optionLongFlags = ["port"] may be set using:

$ ./app --port 443
$ ./app --port=443

optionDefault :: Option a -> aSource

Options may have a default value. This will be parsed as if the user had entered it on the command line.

optionDescription :: Option a -> StringSource

An option's description is used with the default implementation of --help. It should be a short string describing what the option does.

optionGroup :: Option a -> Maybe GroupSource

Which group the option is in. See the "Option groups" section for details.

Option groups

data Group Source

Instances

groupTitle :: Group -> StringSource

A short title for the group, which is used when printing --help output.

groupDescription :: Group -> StringSource

A description of the group, which is used when printing --help output.

Option types

optionType_bool :: OptionType BoolSource

Store an option as a Bool. The option's value must be either "true" or "false".

Boolean options are unary, which means that their value is optional when specified on the command line. If a flag is present, the option is set to True.

$ ./app -q
$ ./app --quiet

Boolean options may still be specified explicitly by using long flags with the --flag=value format. This is the only way to set a unary flag to "false".

$ ./app --quiet=true
$ ./app --quiet=false

optionType_string :: OptionType StringSource

Store an option value as a String. The value is decoded to Unicode first, if needed. The value may contain non-Unicode bytes, in which case they will be stored using GHC 7.4's encoding for mixed-use strings.

optionType_int :: OptionType IntSource

Store an option as an Int. The option value must be an integer n such that minBound <= n <= maxBound.

optionType_int8 :: OptionType Int8Source

Store an option as an Int8. The option value must be an integer n such that minBound <= n <= maxBound.

optionType_int16 :: OptionType Int16Source

Store an option as an Int16. The option value must be an integer n such that minBound <= n <= maxBound.

optionType_int32 :: OptionType Int32Source

Store an option as an Int32. The option value must be an integer n such that minBound <= n <= maxBound.

optionType_int64 :: OptionType Int64Source

Store an option as an Int64. The option value must be an integer n such that minBound <= n <= maxBound.

optionType_word :: OptionType WordSource

Store an option as a Word. The option value must be a positive integer n such that 0 <= n <= maxBound.

optionType_word8 :: OptionType Word8Source

Store an option as a Word8. The option value must be a positive integer n such that 0 <= n <= maxBound.

optionType_word16 :: OptionType Word16Source

Store an option as a Word16. The option value must be a positive integer n such that 0 <= n <= maxBound.

optionType_word32 :: OptionType Word32Source

Store an option as a Word32. The option value must be a positive integer n such that 0 <= n <= maxBound.

optionType_word64 :: OptionType Word64Source

Store an option as a Word64. The option value must be a positive integer n such that 0 <= n <= maxBound.

optionType_integer :: OptionType IntegerSource

Store an option as an Integer. The option value must be an integer. There is no minimum or maximum value.

optionType_float :: OptionType FloatSource

Store an option as a Float. The option value must be a number. Due to the imprecision of floating-point math, the stored value might not exactly match the user's input. If the user's input is out of range for the Float type, it will be stored as Infinity or -Infinity.

optionType_double :: OptionType DoubleSource

Store an option as a Double. The option value must be a number. Due to the imprecision of floating-point math, the stored value might not exactly match the user's input. If the user's input is out of range for the Double type, it will be stored as Infinity or -Infinity.

optionType_maybe :: OptionType a -> OptionType (Maybe a)Source

Store an option as a Maybe of another type. The value will be Nothing if the option is set to an empty string.

optionType_listSource

Arguments

:: Char

Element separator

-> OptionType a

Element type

-> OptionType [a] 

Store an option as a list, using another option type for the elements. The separator should be a character that will not occur within the values, such as a comma or semicolon.

optionType_setSource

Arguments

:: Ord a 
=> Char

Element separator

-> OptionType a

Element type

-> OptionType (Set a) 

Store an option as a Set, using another option type for the elements. The separator should be a character that will not occur within the values, such as a comma or semicolon.

Duplicate elements in the input are permitted.

optionType_mapSource

Arguments

:: Ord k 
=> Char

Item separator

-> Char

Key/Value separator

-> OptionType k

Key type

-> OptionType v

Value type

-> OptionType (Map k v) 

Store an option as a Map, using other option types for the keys and values.

The item separator is used to separate key/value pairs from eachother. It should be a character that will not occur within either the keys or values.

The value separator is used to separate the key from the value. It should be a character that will not occur within the keys. It may occur within the values.

Duplicate keys in the input are permitted. The final value for each key is stored.

optionType_enumSource

Arguments

:: (Bounded a, Enum a, Show a) 
=> String

Option type name

-> OptionType a 

Store an option as one of a set of possible values. The type must be a bounded enumeration, and the type's Show instance will be used to implement the parser.

This is a simplistic implementation, useful for quick scripts. Users with more complex requirements for enum parsing are encouraged to define their own option types using optionType.

data Action = Hello | Goodbye
    deriving (Bounded, Enum, Show)

data MainOptions = MainOptions { optAction :: Action }

instance Options MainOptions where
    defineOptions = pure MainOptions
        <*> defineOption (optionType_enum "action") (\o -> o
            { optionLongFlags = ["action"]
            , optionDefault = Hello
            })

main = runCommand $ \opts args -> do
    putStrLn ("Running action " ++ show (optAction opts))
$ ./app
Running action Hello
$ ./app --action=Goodbye
Running action Goodbye

Custom option types

optionTypeSource

Arguments

:: String

Name

-> val

Default value

-> (String -> Either String val)

Parser

-> (val -> String)

Formatter

-> OptionType val 

Define a new option type with the given name, default, and behavior.

optionTypeName :: OptionType val -> StringSource

The name of this option type; used in --help output.

optionTypeDefault :: OptionType val -> valSource

The default value for options of this type. This will be used if optionDefault is not set when defining the option.

optionTypeParse :: OptionType val -> String -> Either String valSource

Try to parse the given string to an option value. If parsing fails, an error message will be returned.

optionTypeShow :: OptionType val -> val -> StringSource

Format the value for display; used in --help output.

optionTypeUnary :: OptionType val -> Maybe valSource

If not Nothing, then options of this type may be set by a unary flag. The option will be parsed as if the given value were set.