License | MIT |
---|---|
Safe Haskell | Safe-Inferred |
Language | GHC2021 |
Synopsis
- class Options opts where
- defineOptions :: DefineOptions opts
- defaultOptions :: Options opts => opts
- simpleOption :: SimpleOptionType a => String -> a -> String -> DefineOptions a
- data DefineOptions a
- class SimpleOptionType a where
- data Subcommand cmdOpts action
- subcommand :: (Options cmdOpts, Options subcmdOpts) => String -> (cmdOpts -> subcmdOpts -> [String] -> action) -> Subcommand cmdOpts action
- runCommand :: (MonadIO m, Options opts) => (opts -> [String] -> m a) -> m a
- runSubcommand :: (Options opts, MonadIO m) => [Subcommand opts (m a)] -> m a
- class Parsed a
- parsedError :: Parsed a => a -> Maybe String
- parsedHelp :: Parsed a => a -> String
- data ParsedOptions opts
- parsedOptions :: ParsedOptions opts -> Maybe opts
- parsedArguments :: ParsedOptions opts -> [String]
- parseOptions :: Options opts => [String] -> ParsedOptions opts
- data ParsedSubcommand action
- parsedSubcommand :: ParsedSubcommand action -> Maybe action
- parseSubcommand :: Options cmdOpts => [Subcommand cmdOpts action] -> [String] -> ParsedSubcommand action
- data OptionType val
- defineOption :: OptionType a -> (Option a -> Option a) -> DefineOptions a
- data Option a
- optionShortFlags :: Option a -> [Char]
- optionLongFlags :: Option a -> [String]
- optionDefault :: Option a -> a
- optionDescription :: Option a -> String
- optionGroup :: Option a -> Maybe Group
- data Group
- group :: String -> String -> String -> Group
- groupName :: Group -> String
- groupTitle :: Group -> String
- groupDescription :: Group -> String
- optionType_bool :: OptionType Bool
- optionType_string :: OptionType String
- optionType_int :: OptionType Int
- optionType_int8 :: OptionType Int8
- optionType_int16 :: OptionType Int16
- optionType_int32 :: OptionType Int32
- optionType_int64 :: OptionType Int64
- optionType_word :: OptionType Word
- optionType_word8 :: OptionType Word8
- optionType_word16 :: OptionType Word16
- optionType_word32 :: OptionType Word32
- optionType_word64 :: OptionType Word64
- optionType_integer :: OptionType Integer
- optionType_float :: OptionType Float
- optionType_double :: OptionType Double
- optionType_maybe :: OptionType a -> OptionType (Maybe a)
- optionType_list :: Char -> OptionType a -> OptionType [a]
- optionType_set :: Ord a => Char -> OptionType a -> OptionType (Set a)
- optionType_map :: Ord k => Char -> Char -> OptionType k -> OptionType v -> OptionType (Map k v)
- optionType_enum :: (Bounded a, Enum a, Show a) => String -> OptionType a
- optionType :: String -> val -> (String -> Either String val) -> (val -> String) -> OptionType val
- optionTypeName :: OptionType val -> String
- optionTypeDefault :: OptionType val -> val
- optionTypeParse :: OptionType val -> String -> Either String val
- optionTypeShow :: OptionType val -> val -> String
- optionTypeUnary :: OptionType val -> Maybe val
- optionTypeMerge :: OptionType val -> Maybe ([val] -> val)
Defining options
class Options opts where Source #
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
.
defineOptions :: DefineOptions opts Source #
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 => opts Source #
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 a Source #
Defines a new option in the current options type
data DefineOptions a Source #
Instances
Applicative DefineOptions Source # | |
Defined in Options pure :: a -> DefineOptions a # (<*>) :: DefineOptions (a -> b) -> DefineOptions a -> DefineOptions b # liftA2 :: (a -> b -> c) -> DefineOptions a -> DefineOptions b -> DefineOptions c # (*>) :: DefineOptions a -> DefineOptions b -> DefineOptions b # (<*) :: DefineOptions a -> DefineOptions b -> DefineOptions a # | |
Functor DefineOptions Source # | |
Defined in Options fmap :: (a -> b) -> DefineOptions a -> DefineOptions b # (<$) :: a -> DefineOptions b -> DefineOptions a # |
class SimpleOptionType a where Source #
Instances
SimpleOptionType Int16 Source # | |
Defined in Options | |
SimpleOptionType Int32 Source # | |
Defined in Options | |
SimpleOptionType Int64 Source # | |
Defined in Options | |
SimpleOptionType Int8 Source # | |
Defined in Options | |
SimpleOptionType Word16 Source # | |
Defined in Options | |
SimpleOptionType Word32 Source # | |
Defined in Options | |
SimpleOptionType Word64 Source # | |
Defined in Options | |
SimpleOptionType Word8 Source # | |
Defined in Options | |
SimpleOptionType String Source # | |
Defined in Options | |
SimpleOptionType Integer Source # | |
Defined in Options | |
SimpleOptionType Bool Source # | |
Defined in Options | |
SimpleOptionType Double Source # | |
Defined in Options | |
SimpleOptionType Float Source # | |
Defined in Options | |
SimpleOptionType Int Source # | |
Defined in Options | |
SimpleOptionType Word Source # | |
Defined in Options | |
SimpleOptionType a => SimpleOptionType (Maybe a) Source # | |
Defined in Options simpleOptionType :: OptionType (Maybe a) Source # |
Defining subcommands
data Subcommand cmdOpts action Source #
:: (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 a Source #
Either calls the given continuation, prints help text and calls exitSuccess
,
or prints an error and calls exitFailure
.
See runSubcommand
for details on subcommand support.
runSubcommand :: (Options opts, MonadIO m) => [Subcommand opts (m a)] -> m a Source #
Used to run applications that are split into subcommands
Parsing argument lists
See parseOptions
and parseSubcommand
parsedError_, parsedHelp_
Instances
Parsed (ParsedOptions a) Source # | |
Defined in Options parsedError_ :: ParsedOptions a -> Maybe String parsedHelp_ :: ParsedOptions a -> String | |
Parsed (ParsedSubcommand a) Source # | |
Defined in Options parsedError_ :: ParsedSubcommand a -> Maybe String parsedHelp_ :: ParsedSubcommand a -> String |
parsedError :: Parsed a => a -> Maybe String Source #
Get the error that prevented options from being parsed from argv,
or Nothing
if no error was detected
parsedHelp :: Parsed a => a -> String Source #
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
data ParsedOptions opts Source #
See parseOptions
Instances
Parsed (ParsedOptions a) Source # | |
Defined in Options parsedError_ :: ParsedOptions a -> Maybe String parsedHelp_ :: ParsedOptions a -> String |
parsedOptions :: ParsedOptions opts -> Maybe opts Source #
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 occurred 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 opts Source #
Attempt to convert a list of command-line arguments into an options value
Parsing sub-commands
data ParsedSubcommand action Source #
See parseSubcommand
Instances
Parsed (ParsedSubcommand a) Source # | |
Defined in Options parsedError_ :: ParsedSubcommand a -> Maybe String parsedHelp_ :: ParsedSubcommand a -> String |
parsedSubcommand :: ParsedSubcommand action -> Maybe action Source #
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 occurred during parsing, check the value of parsedError
.
parseSubcommand :: Options cmdOpts => [Subcommand cmdOpts action] -> [String] -> ParsedSubcommand action Source #
Attempt to convert a list of command-line arguments into a subcommand action
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 a Source #
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 })
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 -> a Source #
Options may have a default value. This will be parsed as if the user had entered it on the command line.
optionDescription :: Option a -> String Source #
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 Group Source #
Which group the option is in. See the "Option groups" section for details.
Option groups
:: String | Name |
-> String | Title; see |
-> String | Description; see |
-> Group |
Define an option group with the given name and title
Use groupDescription
to add additional descriptive text, if needed.
groupTitle :: Group -> String #
A short title for the group, which is used when printing
--help
output.
groupDescription :: Group -> String #
A description of the group, which is used when printing
--help
output.
Option types
optionType_bool :: OptionType Bool Source #
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.
optionType_string :: OptionType String Source #
Store an option value as a String
The value is decoded to Unicode first, if needed.
optionType_integer :: OptionType Integer Source #
Store an option as an Integer
The option value must be an integer. There is no minimum or maximum value.
optionType_maybe :: OptionType a -> OptionType (Maybe a) Source #
Store an option as a
of another typeMaybe
The value will be Nothing
if the option is set to an empty string.
:: 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.
:: Ord a | |
=> Char | Element separator |
-> OptionType a | Element type |
-> OptionType (Set a) |
Store an option as a
, using another option type for the elementsSet
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.
:: 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 each other. 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.
:: (Bounded a, Enum a, Show a) | |
=> String | Option type name |
-> OptionType a |
Store an option as one of a set of possible values
This is a simplistic implementation, useful for quick scripts.
For more possibilities, see optionType
.
Custom option types
:: 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 -> String Source #
The name of this option type; used in --help
output.
optionTypeDefault :: OptionType val -> val Source #
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 val Source #
Try to parse the given string to an option value. If parsing fails, an error message will be returned.
optionTypeShow :: OptionType val -> val -> String Source #
Format the value for display; used in --help
output.
optionTypeUnary :: OptionType val -> Maybe val Source #
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.
optionTypeMerge :: OptionType val -> Maybe ([val] -> val) Source #
If not Nothing, then options of this type may be set with repeated
flags. Each flag will be parsed with optionTypeParse
, and the
resulting parsed values will be passed to this function for merger
into the final value.