Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module implements a lightweight flags parser, inspired by optparse-applicative
.
Sample usage (note the default log level and optional context):
module Main where import Control.Applicative ((<|>), optional) import Data.Text (Text) import Flags.Applicative data Flags = Flags { rootPath :: Text , logLevel :: Int , context :: Maybe Text } deriving Show flagsParser :: FlagsParser Flags flagsParser = Flags <$> flag textVal "root" "path to the root" <*> (flag autoVal "log_level" "" <|> pure 0) <*> (optional $ flag textVal "context" "") main :: IO () main = do (flags, args) <- parseSystemFlagsOrDie optionsParser print flags
Synopsis
- type Name = Text
- type Description = Text
- switch :: Name -> Description -> FlagsParser ()
- boolFlag :: Name -> Description -> FlagsParser Bool
- flag :: Reader a -> Name -> Description -> FlagsParser a
- type Reader a = Text -> Either String a
- autoVal :: Read a => Reader a
- textVal :: Reader Text
- fracVal :: Fractional a => Reader a
- intVal :: Integral a => Reader a
- enumVal :: (Bounded a, Enum a, Show a) => Reader a
- hostVal :: Reader (HostName, Maybe PortNumber)
- listOf :: Reader a -> Reader [a]
- mapOf :: Ord a => Reader a -> Reader b -> Reader (Map a b)
- data FlagsParser a
- data FlagsError
- parseFlags :: FlagsParser a -> [String] -> Either FlagsError (a, [String])
- parseSystemFlagsOrDie :: FlagsParser a -> IO (a, [String])
Declaring flags
The name of a flag (without the --
prefix). Names can use all valid utf-8 characters except
=
(the value delimiter). In general, it's good practice for flag names to be lowercase ASCII
with underscores.
The following names are reserved and attempting to define a flag with the same name will cause an error:
help
, displays usage when set.swallowed_flags
, flags in this list which are set but undeclared will be ignored rather than cause an error during parsing.swallowed_switches
, similar toswallowed_flags
but for switches (nullary flags).
type Description = Text Source #
An human-readable explanation of what the flag does. It is displayed when the parser is invoked
with the --help
flag.
Nullary flags
switch :: Name -> Description -> FlagsParser () Source #
Returns a parser with the given name and description for a flag with no value, failing if the
flag is not present. See also boolFlag
for a variant which doesn't fail when the flag is
missing.
boolFlag :: Name -> Description -> FlagsParser Bool Source #
Returns a parser with the given name and description for a flag with no value, returning whether the flag was present.
Unary flags
flag :: Reader a -> Name -> Description -> FlagsParser a Source #
Returns a parser using the given value reader, name, and description for a flag with an associated value.
Common readers
fracVal :: Fractional a => Reader a Source #
Returns a reader for any number with a Fractional
instance (e.g. Double
, Float
).
enumVal :: (Bounded a, Enum a, Show a) => Reader a Source #
Returns a reader for Enum
instances. This reader assumes that enum (Haskell) constructors are
written in PascalCase and expects UPPER_SNAKE_CASE as command-line flag values. For example:
data Mode = Flexible | Strict deriving (Bounded, Enum, Show) modeFlag = flag enumVal "mode" "the mode" :: FlagsParser Mode
The above flag will accept values --mode=FLEXIBLE
and --mode=STRICT
.
hostVal :: Reader (HostName, Maybe PortNumber) Source #
Returns a reader for network hosts of the form hostname:port
. The port part is optional.
Reader combinators
listOf :: Reader a -> Reader [a] Source #
Transforms a single-valued unary flag into one which accepts multiple comma-separated values. For example, to parse a comma-separated list of integers:
countsFlag = flag (listOf intVal) "counts" "the counts"
Empty text values are ignored, which means both that trailing commas are supported and that an empty list can be specified simply by specifying an empty value on the command line. Note that escapes are not supported, so values should not contain any commas.
mapOf :: Ord a => Reader a -> Reader b -> Reader (Map a b) Source #
Transforms a single-valued unary flag into one which accepts a comma-separated list of
colon-delimited key-value pairs. The syntax is key:value[,key:value...]
. Note that escapes are
not supported, so neither keys not values should contain colons or commas.
Running parsers
data FlagsParser a Source #
Flags parser.
There are two types of flags:
- Nullary flags created with
switch
andboolFlag
, which do not accept a value. - Unary flags created with
flag
. These expect a value to be passed in either after an equal sign (--foo=value
) or as the following input value (--foo value
). If the value starts with--
, only the first form is accepted.
You can run a parser using parseFlags
or parseSystemFlagsOrDie
.
Instances
Functor FlagsParser Source # | |
Defined in Flags.Applicative fmap :: (a -> b) -> FlagsParser a -> FlagsParser b # (<$) :: a -> FlagsParser b -> FlagsParser a # | |
Applicative FlagsParser Source # | |
Defined in Flags.Applicative pure :: a -> FlagsParser a # (<*>) :: FlagsParser (a -> b) -> FlagsParser a -> FlagsParser b # liftA2 :: (a -> b -> c) -> FlagsParser a -> FlagsParser b -> FlagsParser c # (*>) :: FlagsParser a -> FlagsParser b -> FlagsParser b # (<*) :: FlagsParser a -> FlagsParser b -> FlagsParser a # | |
Alternative FlagsParser Source # | |
Defined in Flags.Applicative empty :: FlagsParser a # (<|>) :: FlagsParser a -> FlagsParser a -> FlagsParser a # some :: FlagsParser a -> FlagsParser [a] # many :: FlagsParser a -> FlagsParser [a] # |
data FlagsError Source #
The possible parsing errors.
DuplicateFlag Name | A flag was declared multiple times. |
EmptyParser | The parser was empty. |
Help Text | The input included the |
InconsistentFlagValues Name | At least one unary flag was specified multiple times with different values. |
InvalidFlagValue Name Text String | A unary flag's value failed to parse. |
MissingFlags (NonEmpty Name) | A required flag was missing; at least one of the returned flags should be set. |
MissingFlagValue Name | A unary flag was missing a value. This can happen either if a value-less unary flag was the
last token or was followed by a value which is also a flag name (in which case you should use
the single-token form: |
ReservedFlag Name | A flag with a reserved name was declared. |
UnexpectedFlagValue Name | A nullary flag was given a value. |
UnexpectedFlags (NonEmpty Name) | At least one flag was set but unused. This can happen when optional flags are set but their branch is not selected. |
UnknownFlag Name | An unknown flag was set. |
Instances
Eq FlagsError Source # | |
Defined in Flags.Applicative (==) :: FlagsError -> FlagsError -> Bool # (/=) :: FlagsError -> FlagsError -> Bool # | |
Show FlagsError Source # | |
Defined in Flags.Applicative showsPrec :: Int -> FlagsError -> ShowS # show :: FlagsError -> String # showList :: [FlagsError] -> ShowS # |
parseFlags :: FlagsParser a -> [String] -> Either FlagsError (a, [String]) Source #
Runs a parser on a list of tokens, returning the parsed flags alongside other non-flag
arguments (i.e. which don't start with --
). If the special --
token is found, all following
tokens will be considered arguments even if they look like flags.
parseSystemFlagsOrDie :: FlagsParser a -> IO (a, [String]) Source #
Runs a parser on the system's arguments, or exits with code 1 and prints the relevant error message in case of failure.