hsoptions-1.0.0.0: Haskell library that supports command-line flag processing

Portabilityportable
Stabilitystable
MaintainerJose Raymundo Cruz (jose.r.cruz01@gmail.com)
Safe HaskellNone

System.Console.HsOptions

Contents

Description

HsOptions library supports command line flag parsing.

Too see an user guide and list of features go to https://github.com/josercruz01/hsoptions#table-of-contents.

Flags are declared in the code by using the make function, which takes the flag's name, help text and type as arguments.

The flags are parsed from the command line stream of from a configuration file if the --usingFile <filename> flag is sent to the program.

A configuration file is just a text document that defines command line arguments for our program in the standard command line syntax. This is a simple configuration file example that defines two flags and three positional arguments and also includes a second configuration file:

 # confFile1.txt
--user_id = 8
--user_name = batman
--usingFile tmplocalConfiguration.txt
arg1
arg2
arg3

So doing this:

>>> runhaskell Prog.hs --usingFile confFile1.txt

Is equivalent to doing this

>>> runhaskell Prog.hs --user_id = 8 --user_name = batman ... arg2 arg3

Flags can be customized by calling configuration function, such as defaultIs or aliasIs, that change how the flag behaves, how it is parsed and validated.

The processMain function needs to be called at the beginning of the main function. This function takes as arguments:

  • The program description
  • A list of all declared flags
  • Success callback function
  • Failure callback function
  • Display-Help callback function

If there is any kind of validation error failure is called with the list of errors. If the --help flag was sent by the user display help is called. Otherwise if there are no problems the success function is called.

A default implementation of failure and display help is provided in the library (defaultDisplayHelp, defaultDisplayErrors) with a basic behavior.

Basically, success becomes the 'real' main function. It takes as argument a tuple (FlagResults, ArgsResults). FlagResults is a data structure that can be used to query flags by using the get function. ArgsResults is just an array of String containing the remaining not-flag arguments.

A simple example (more in https://github.com/josercruz01/hsoptions/tree/master/examples)

 import System.Console.HsOptions

 userName = make ( "user_name",
                 , "the user name of the app",
                 , [ parser stringParser,
                   , aliasIs ["u"]
                   ]
                 )
 userAge = make ("age", "the age of the user", [parser intParser])

 flagData = combine [flagToData userName, flagToData userAge]

 main :: IO ()
 main = processMain "Simple example for HsOptions."
                    flagData
                    success
                    failure
                    defaultDisplayHelp

 success :: ProcessResults -> IO ()
 success (flags, args) = do let nextAge = (flags `get` userAge) + 5
                            putStrLn ("Hello " ++ flags `get` userName)
                            putStrLn ("In 5 years you will be " ++
                                      show nextAge ++
                                      " years old!")

 failure :: [FlagError] -> IO ()
 failure errs = do putStrLn "Some errors occurred:"
                   mapM_ print errs

At the processMain function each of the input flags is validated against the declared flags. Within the success function you can be sure that all required flags exist, all flag types are correct and all validation was successful.

Synopsis

Definition of flags

make :: (String, String, [FlagConf a]) -> Flag aSource

Defines a flag.

A defined flag consist of a name, a helptext and a list of flag configurations. The name is the flag identifier, it must be unique among all other defined flags.

The name must follow the pattern " 'Letter' followed by many 'Letters || Numbers || Dashes (-) || Underscores (_)' ". If the name of the flag is invalid an exception is thrown.

A parser for the flag must be set in the configuration by using parser or maybeParser. If a parser is not found an exception is thrown.

Arguments:

  • (name, helptext, configurations): A triple containing the flag name, the helptext and the flag configurations.

Returns:

  • A flag.

Throws:

  • An exception if the name is invalid (does not follows the pattern).
  • An exception if the parser was not set in the configurations.

Query flag values

get :: FlagResults -> Flag a -> aSource

Method to get a flag value out of a FlagResults.

This is the method used to get the proper value for each flag after the input stream has been processed. The processMain method will create the FlagResults data structure for a set of defined flags.

This is an example on how to use this method:

 user_id :: Flag Int
 user_id = make ("user_id", "help", [parser intParser]

 main_success :: (FlagResults, ArgsResults) -> IO ()
 main_success (flags, _) = putStrLn ("Next user id: " ++
                                    show ((get flags user_id) + 1)))

Arguments:

  • flag_results: the FlagResults created from the input stream.

Returns:

  • The value of the given flag.

Throws:

  • An exception is raised if flag does not exist in the FlagResults. At this point, the get method should always succeed parsing a flag value. If the flag is not found then that means that the flag was not processed by the parser, possibly because the flag was not added to the FlagData sent to the processor.

Process flags

processMain :: String -> FlagData -> (ProcessResults -> IO ()) -> ([FlagError] -> IO ()) -> (String -> [(String, [String], String)] -> IO ()) -> IO ()Source

Processes the input arguments and parses all the flags.

Starts the process flags pipeline. First checks if the user wants to display the help text of the program. This is done by looking for the flag "--help" or "-h" flag in the input stream. If this flag is found then the display_help function is called with all the compiled helptext and the program description.

If the user does not wants to display the help then the process function is called to do the actual flag parsing. This function can return errors or a success result (FlagResults, ArgsResults). If any error is found then the failure function is called with the list of errors, otherwise the success function is called with the results.

See the process documentation to see the rules and conditions of flag parsing.

Arguments:

  • description: the description of the program. Sent to the display_help function.
  • flag_data: a collection of all the flags defined in the code.
  • success: a success callback function. Called if no errors were found while parsing the flags from the input.
  • failure: a failure callback function. Called if some errors were found while parsing the input.
  • display_help: a display help callback function. Called when the "--help" or "-h" flag was sent by the user.

Returns:

  • An IO action.

process :: FlagData -> [String] -> IO (Either [FlagError] ProcessResults)Source

Does the actual flag parsing.

It begins by parsing the entire input stream and creating a tokenized input stream. A recursive search is done in these tokens to find any configuration files includes. Each conf file include is expanded until the tokenized stream is just composed of flags and positional arguments.

This tokenized stream is validated then by the rules of each flag, such as type validation, required flags, constraints, etc.

This method is an IO action because it needs to expand the configuration file includes (open the file and get it's content). When the stream is tokenized and no more IO is needed the 'process\'' method is called.

The validation is divided in two, local validation and global validation.

Local validation handled things like reserved words, unknown flags and correct flag types.

Global validation happens at the end and does all the validation that needs a context, such as global validation constraints, conditionally required flags and dependent default. Global validation only happens if the local validation succeeds.

Arguments:

  • flag_data: a set of all the flags to process.
  • input_stream: the command line input stream.

Returns:

  • Either a list of errors (Left) or a successful result (Right).

process' :: FlagData -> [Token] -> Either [FlagError] ProcessResultsSource

Does the actual flag parsing after the input stream have been tokenized and the configuration files have been expanded.

Updates the tokenized input stream and changes any flag alias set by the user to the actual name of the flag, meaning if the user sent --uid = 8 then the token is changed to --user_id = 8 (considering uid is an alias for user_id). This means from this point forward the flag name is used as the flag identifier (any alias was mapped to the flag name).

Performs local validation:

  • Verifies that no reserved words was used for the flag's name.
  • Validates that no unknown flag was sent by the user.
  • Validates that for every value set to a flag this value can be parsed to the type the flag is expecting. (i.e. checks the string value of an Int flag can be parsed from string to Int correctly).

Performs global validation:

  • Validates the requiredIf constraints.
  • Validates the defaultIf constraints.
  • Validates all global validation rules are passing (rules created by using the validate function)

Arguments:

  • flag_data: a set of all the flags to process.
  • tokenized_input_stream: the complete input stream after tokenized.

Returns: * Either a list of errors (Left) or a successful result (Right).

flagToData :: Flag a -> FlagDataSource

Converts a Flag to a FlagData.

FlagData is the general form of the flag that is not bounded by the type "a" of the "Flag a" input, thus it can be added to a collection of flags later.

Arguments:

  • flag: the flag to be mapped.

Returns:

  • A corresponding FlagData for the flag.

combine :: [FlagData] -> FlagDataSource

Takes a list of FlagData and combines them together into a single FlagData.

Validates that a flag name is not repeated in the incoming list of flag data.

Usage example:

 flagData = combine [ flagToData user_id
                    , flagToData user_name,
                    , flagToData database
                    ]

Arguments:

  • flag_data_list: list of flag data to combine.

Returns:

Throws:

  • An exception if any two flag names are duplicated in the input flag_data_list.

Default functions

defaultDisplayHelp :: String -> [(String, [String], String)] -> IO ()Source

Prints the help text to the screen using an standard format.

Arguments:

  • description: the description of the program.
  • flag_helptexts: A list of triples (name, aliases, helptext) that contains an entry for each flag, with the flag's name, aliases and helptext.

defaultDisplayErrors :: [FlagError] -> IO ()Source

Displaye the list of errors to the screen.

Arguments:

  • errors: list of errors to display.

Flag configurations

parser :: (FlagArgument -> Maybe a) -> FlagConf aSource

Sets the flag's parser configuration.

It takes the function that will parse the string input to the corresponding flag type value. A set of this functions, such as intParser, was created to provide a basic set of parsers.

Arguments:

  • parser_function: a function that takes a flag argument and returns Nothing if the argument can not be parsed or the parsed value (Just) if the argument can be parsed correctly.

Returns:

  • A flag configuration that defines how to parse the string input.

maybeParser :: (FlagArgument -> Maybe a) -> FlagConf (Maybe a)Source

Combination of the parser and toMaybeParser for syntactic sugar since this is a very common scenario.

Basically is defined as:

 maybeParser = parser . toMaybeParser

So instead of always doing:

>>> user_id = make ("user_id", "help", [parser $ toMaybeParser intParser])

You can do:

>>> user_id = make ("user_id", "help", [maybePaser intParser])

Arguments:

  • parser_function: parser function that defines how to parse the string input to the flag's value.

Returns:

  • A flag configuration that sets how to parse the string input.

isOptional :: FlagConf (Maybe a)Source

Creates a flag configuration that makes the flag as optional.

Since the flag is optional then it's type must bet Flag (Maybe a), so that it can be Nothing if the flag was not provided by the user or Just value if it was provided.

Returns:

  • A flag configuration that marks the flag as optional. This method is a specification of the requiredIf method. Is is equivalent to:
>>> requiredIf (const False)

emptyValueIs :: a -> FlagConf aSource

Creates a flag configuration that defines the default value when the flag is empty.

Sets the value a flag should take if it is the case that this flag was provided by the user but not it's value (i.e. runhaskell Program.hs --user_id).

Arguments:

  • empty_value: the value to use if the flag value is empty.

Returns:

  • A flag configuration that sets the flag's empty value.

defaultIs :: a -> FlagConf aSource

Creates a flag configuration that sets sets the default value for a flag if the flag is not provided by the user.

Arguments:

  • default value: the default value of the flag.

Returns:

  • A flag configuration that sets the flag's default value. This method is a specification of the defaultIs method. Is is equivalent to:
>>> defaultIf a (const True)

defaultIf :: (FlagResults -> Maybe a) -> FlagConf aSource

Creates a flag configuration that sets a dependent default value for a flag.

This configuration requires a function that takes in a FlagResults as argument and returns a `Maybe a` value, Nothing says that there is no default value and `Just something` says that there is a default value.

Arguments:

  • default_getter: function that given a FlagResults returns the default value (Just) or Nothing if no default value exist;

Returns:

  • A flag configuration that sets the dependent default value for the flag.

aliasIs :: [String] -> FlagConf aSource

Creates a flag configuration for the aliases of the flag.

Sets multiple alias for a single flag. (i.e. --user_id alias: ["u", "uid","user_identifier"]). These aliases can be used to set the flag value, so --user_id = 8 is equivalent to -u = 8.

Arguments:

  • aliases: the alias list for the flag.

Returns:

  • A flag configuration that sets the aliases for a given flag.

requiredIf :: (FlagResults -> Bool) -> FlagConf (Maybe a)Source

Creates a flag configuration that marks a flag as conditionally required.

The flag will be required from the user if the condition returns True and the user does not provides the flag in the input stream, a "flag is required" error is displayed in this scenario.

The flag type must be Maybe a, if the condition returns False and the flag is not provided then it's value is Nothing. On the other hand if the flag is provided it's value will be Just value.

Arguments:

  • condition: the condition to determine if the flag is required.

Returns:

  • A flag configuration that sets the conditional flag required constraint.

Flag parsers

intParser :: FlagArgument -> Maybe IntSource

Parses an Int from the input FlagArgument

Arguments:

  • argument: the input argument

Returns:

  • Nothing if the argument cannot be parsed to the type or the parsed value (Just) if it can.

floatParser :: FlagArgument -> Maybe FloatSource

Parses an Float from the input FlagArgument

Arguments:

  • argument: the input argument

Returns:

  • Nothing if the argument cannot be parsed to the type or the parsed value (Just) if it can.

doubleParser :: FlagArgument -> Maybe DoubleSource

Parses an Double from the input FlagArgument

Arguments:

  • argument: the input argument

Returns:

  • Nothing if the argument cannot be parsed to the type or the parsed value (Just) if it can.

charParser :: FlagArgument -> Maybe CharSource

Parses a Char from the input FlagArgument

Arguments:

  • argument: the input argument

Returns:

  • Nothing if the argument cannot be parsed to the type or the parsed value (Just) if it can.

stringParser :: FlagArgument -> Maybe StringSource

Parses a String from the input FlagArgument

Arguments:

  • argument: the input argument

Returns:

  • Nothing if the argument cannot be parsed to the type or the parsed value (Just) if it can.

boolParser :: FlagArgument -> Maybe BoolSource

Parses a Bool from the input FlagArgument

Arguments:

  • argument: the input argument

Returns:

  • False (Just) if the flag is missing.
  • True (Just) if the flag value is missing.
  • Nothing if the argument cannot be parsed to the type or the parsed value (Just) if it can.

arrayParser :: Read a => FlagArgument -> Maybe [a]Source

Parses an Array from the input FlagArgument

Arguments:

  • argument: the input argument

Returns:

  • Nothing if the argument cannot be parsed to the type or the parsed value (Just) if it can.

boolFlag :: [FlagConf Bool]Source

A predefined set of flag configurations for a boolean flag.

Defines a set of configurations that specifies:

This defines a default boolean flag behavior such that if the flag is missing then it is treated as False, if the flag is present (i.e --help) then it is True.

toMaybeParser :: (FlagArgument -> Maybe a) -> FlagArgument -> Maybe (Maybe a)Source

Wraps a parser function that takes a FlagArgument and returns a "Maybe a" and converts it to a function that returns a "Maybe (Maybe a)".

This new function does will never fail if the argument is missing or if the argument value is missing (FlagMissing or FlagValueMissing), instead this function maps any of these two to a Nothing value.

If the flag argument is of type FlagValue then the original parser is used.

It is a convenient way to reuse current parsers, like intParser, without having to redefine them. For instance "intParser" is of type FlagArgument -> (Maybe Int), but "toMaybeParser intParser" is of type FlagArgument -> (Maybe (Maybe Int)).

Usage example:

 user_id :: Flag (Maybe Int)
 user_id = make ("user_id", "help", [parser (toMaybeParser intParser)])

As you can observe intParser was reused.

Arguments:

  • original_parser: the original parser to be wrapped.

Returns:

  • A new parser that changes the result type to an optional type.

Global validation

validate :: GlobalRule -> FlagDataSource

Constructs a FlagData out of a GlobalRule.

This global rule will be used in the last validation stage of the process method.

Usage example:

 flagData = combine [ flagToData user_id
                     , validate (\fr -> if get fr user_id < 0
                                       then Just "user id negative error"
                                       else Nothing)
                    ]

Multiple validation rules can exist.

Arguments:

  • global_rule: global validation rule

Returns:

  • A FlagData representation of the global_rule.

Flag operations

operation :: OperationToken -> FlagConf aSource

Creates a flag configuration for the default operation of the flag.

Defines the default operation for the flag if no operation is made explicit by the user. If this method is not called then the default operation is always assign.

>>> runhaskell Program.hs --user_name += batman
Operation was explicit: Operation = "Append operation"
>>> runhaskell Program.hs --user_name batman
Operation not specified: Operation = @default_operation@

Arguments:

  • default_operation: operation to use if no operation is provided for the flag in the input stream.

Returns:

  • A flag configuration that sets the default operation of the flag.

assign :: OperationTokenSource

Assign operation (=). Default flag operation if no operation is set.

Sets the flag value to the current value, overwriting any previous value the flag may have.

>>> operation assign
Sets the default operation for the flag to assign

Returns:

  • Assign flag operation.

append :: OperationTokenSource

Append operation (+=). One of the available flag operations.

The flag value is appended with it's previous value using a space in between values. It is used as the argument of operation function:

>>> operation append
Sets the default operation for the flag to append

Returns:

  • Append flag operation.

append' :: OperationTokenSource

Append' operation (+=!). One of the available flag operations.

Same as append but appends with no space in between. It is used as the argument of operation function:

>>> operation append'
Sets the default operation for the flag to append'

Returns:

  • Append' flag operation.

prepend :: OperationTokenSource

Prepend operation (=+). One of the available flag operations.

The flag value is prepended with it's previous value using a space in between values. It is used as the argument of operation function:

>>> operation prepend
Sets the default operation for the flag to prepend

Returns:

  • Prepend flag operation.

prepend' :: OperationTokenSource

Prepend' operation (=+!). One of the available flag operations.

Same as prepend but appends with no space in between. It is used as the argument of operation function:

>>> operation prepend'
Sets the default operation for the flag to prepend'

Returns:

  • Prepend' flag operation.

Data types

data Flag a Source

Data type that represents a defined flag. It contains:

  • the name of the flag * help text for the flag * list of configurations for the flags such as type, default values, etc.

type FlagData = (FlagDataMap, FlagAliasMap, [GlobalRule])Source

Type that represents a collection of all defined flags.

It has three components:

  • A flag map: The key is the flag name and the value is the flag data * An alias map: A map that connects any flag alias with it's unique flag name. This is used to convert each flag alias to it's flag name when parsing. * A list of global validation rules

data FlagError Source

Data type for a flag error. It will contain the error message and what kind of error occurred:

  • FatalError: an error that the system can't recover from * NonFatalError: an error that does not stop the process

Instances

Show FlagError

Making FlagError an instance of Show

type FlagResults = Map String FlagArgumentSource

Type that represents the final result of the parse process.

It maps a flag name to it's value. This value is of type FlagArgument, which means that it can be empty or not.

This type is used by the user to get each flag value in the main method by using the get method and passing a flag variable.

data FlagArgument Source

Data type that represents an input flag argument.

It's type will vary depending on the user input. For example if the user calls the program that expects the user_id flag:

>>> ./runhaskell Program.hs
FlagArgument = FlagMissing "user_id"
>>> ./runhaskell Program.hs --user_id
FlagArgument = FlagValueMissing "user_id"'
>>> ./runhaskell Program.hs --user_id 8
FlagArgument = FlagValue "user_id" "8"

Constructors

FlagMissing String

argument not provided

FlagValueMissing String

argument provided but not it's value

FlagValue String String

argument with value provided

type GlobalRule = FlagResults -> Maybe StringSource

Type that represents a global validation rule for a FlagResults.

It is used to create global validation after the flags are processed. If the result is a Nothing then the rule passed. Otherwise if a Just err' is returned then the ruled failed with the message "err".

type ProcessResults = (FlagResults, ArgsResults)Source

Type of the return value of the process function and it's sub-functions.

type ArgsResults = [String]Source

Type that is the list of remaining positional arguments after the parse process is completed. For example:

 ./runhaskell Program.hs --user_id 8 one two three

ArgsResults will contain the list ["one", "two", "three"]

data FlagConf a Source

Data type that represent a flag configuration.

It is used when a flag is created to set the type of the flag, how it is parsed, if the flag is required or optional, etc.