flags-applicative-0.0.4.0: Applicative flag parsing

Safe HaskellSafe
LanguageHaskell2010

Flags.Applicative

Contents

Description

Simple flags parsing module, 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 Options = Options
  { rootPath :: Text
  , logLevel :: Int
  , context :: Maybe Text
  } deriving Show

optionsParser :: FlagParser Options
optionsParser = Options <$> textFlag "root" "path to the root"
                        <*> (autoFlag "log_level" "" <|> pure 0)
                        <*> (optional $ textFlag "context" "")

main :: IO ()
main = do
  (opts, args) <- parseSystemFlagsOrDie optionsParser
  print opts
Synopsis

Documentation

type Name = Text Source #

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 to swallowed_flags but for switches (nullary flags).

type Description = Text Source #

An human-readable explanation of what the flag does.

data FlagParser a Source #

Flags parser.

There are two types of flags:

  • Nullary flags created with 'switch which are True when set and False otherwise. For example --version or --enable_foo.
  • Unary flags created with unaryFlag and its convenience variants (e.g. textFlag, flag, repeatedFlag). 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.

Instances
Functor FlagParser Source # 
Instance details

Defined in Flags.Applicative

Methods

fmap :: (a -> b) -> FlagParser a -> FlagParser b #

(<$) :: a -> FlagParser b -> FlagParser a #

Applicative FlagParser Source # 
Instance details

Defined in Flags.Applicative

Methods

pure :: a -> FlagParser a #

(<*>) :: FlagParser (a -> b) -> FlagParser a -> FlagParser b #

liftA2 :: (a -> b -> c) -> FlagParser a -> FlagParser b -> FlagParser c #

(*>) :: FlagParser a -> FlagParser b -> FlagParser b #

(<*) :: FlagParser a -> FlagParser b -> FlagParser a #

Alternative FlagParser Source # 
Instance details

Defined in Flags.Applicative

data FlagError Source #

The possible parsing errors.

Constructors

DuplicateFlag Name

A flag was declared multiple times.

EmptyParser

The parser was empty.

Help Text

The input included the --help flag.

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.

MissingFlag Name

A required flag was missing.

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: --flag=--value).

ReservedFlag Name

A flag with a reserved name was declared.

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 FlagError Source # 
Instance details

Defined in Flags.Applicative

Show FlagError Source # 
Instance details

Defined in Flags.Applicative

parseFlags :: FlagParser a -> [String] -> Either FlagError (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 :: FlagParser 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.

Defining flags

switch :: Name -> Description -> FlagParser () Source #

Returns a parser with the given name and description for a flag with no value.

boolFlag :: Name -> Description -> FlagParser Bool Source #

Returns a parser with the given name and description for a flag with no value.

flag :: (Text -> Either String a) -> Name -> Description -> FlagParser a Source #

Returns a parser using the given parsing function, name, and description for a flag with an associated value.

textFlag :: Name -> Description -> FlagParser Text Source #

Returns a parser for a single text value.

autoFlag :: Read a => Name -> Description -> FlagParser a Source #

Returns a parser for any value with a Read instance. Prefer textFlag for textual values since flag will expect its values to be double-quoted and might not work as expected.

textListFlag :: Text -> Name -> Description -> FlagParser [Text] Source #

Returns a parser for a multiple text value.

autoListFlag :: Read a => Text -> Name -> Description -> FlagParser [a] Source #

Returns a parser for multiple values with a Read instance, with a configurable separator. Empty values are always ignored, so it's possible to declare an empty list as --list= and trailing commas are supported.