flags-applicative-0.0.1.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 Data.Text.Read (decimal)
import Flags.Applicative
import System.Environment (getArgs)

data Options = Options
  { rootPath :: Text
  , logLevel :: Int
  , context :: Maybe Text
  } deriving Show

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

main :: IO ()
main = do
  args <- getArgs
  print $ parseFlags optionsParser args
Synopsis

Documentation

type Name = Text Source #

The name of a flag, can use all characters but = (the value delimiter). It's good practice for flag names to be lowercase ASCII with underscores.

data FlagParser a Source #

Flags parser.

There are two types of flags:

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

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.

InvalidParser ParserError

The parser is invalid. Unlike other FlagError constructors, this indicates an issue with the parser's declaration (rather than the input tokens).

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).

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

data ParserError Source #

Parser definition errors.

Constructors

DuplicateFlag Name

The same flag name was declared multiple times.

Empty

The parser is empty (this should not happen if you use standard combinators).

Instances
Eq ParserError Source # 
Instance details

Defined in Flags.Applicative

Show ParserError Source # 
Instance details

Defined in Flags.Applicative

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

Nullary flags

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

Returns a nullary parser with the given name and description.

Unary flags

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

Returns a unary parser using the given parsing function, name, and description.

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

Returns a flag with Text values.

numericFlag :: Reader a -> Name -> Text -> FlagParser a Source #

Returns a flag which can parse numbers using the helper methods in Data.Text.Read (e.g. decimal).