registry-options-0.2.0.0: application options parsing
Safe HaskellSafe-Inferred
LanguageGHC2021

Data.Registry.Options.Parser

Description

Main module for creating option parsers

Synopsis

Documentation

data Parser (s :: Symbol) a Source #

A Parser is responsible for parsing a value of type a for to be used as "s" where s is a Symbol For example "s" can be the name of a field, force in a data type

A Parser generally returns all the original lexemes values minus the option name and value just parsed This is a bit different for positional arguments for example where the whole list of lexemes values is kept

Constructors

Parser 

Instances

Instances details
Alternative (Parser s) Source # 
Instance details

Defined in Data.Registry.Options.Parser

Methods

empty :: Parser s a #

(<|>) :: Parser s a -> Parser s a -> Parser s a #

some :: Parser s a -> Parser s [a] #

many :: Parser s a -> Parser s [a] #

Applicative (Parser s) Source # 
Instance details

Defined in Data.Registry.Options.Parser

Methods

pure :: a -> Parser s a #

(<*>) :: Parser s (a -> b) -> Parser s a -> Parser s b #

liftA2 :: (a -> b -> c) -> Parser s a -> Parser s b -> Parser s c #

(*>) :: Parser s a -> Parser s b -> Parser s b #

(<*) :: Parser s a -> Parser s b -> Parser s a #

Functor (Parser s) Source # 
Instance details

Defined in Data.Registry.Options.Parser

Methods

fmap :: (a -> b) -> Parser s a -> Parser s b #

(<$) :: a -> Parser s b -> Parser s a #

data Positional Source #

This data type indicates if an argument must be parsed at a specific position This changes the parsing since positional arguments do not consume lexemes

Constructors

Positional 
NonPositional 

Instances

Instances details
Show Positional Source # 
Instance details

Defined in Data.Registry.Options.Parser

Eq Positional Source # 
Instance details

Defined in Data.Registry.Options.Parser

unitParser :: Parser s () Source #

This parser does not consume anything but always succeeds. It is a unit for the *> operator

addParserHelp :: Help -> Parser s a -> Parser s a Source #

Add some help description to a Parser

setParserHelp :: Help -> Parser s a -> Parser s a Source #

Set some help description on a Parser

getOptionNames :: Parser s a -> [Text] Source #

Retrieve all the option names for this parser by extracting the help and collecting option names for the top level command and the subcommands

type Command = "Command" Source #

The Command type can be used to create parsers which are not given a specific role

coerceParser :: Parser s a -> Parser t a Source #

All parsers can be used to parse a command

parseArgs :: Parser s a -> [Text] -> Either Text a Source #

Command line arguments can be parsed with a specific and either return an error if there is nothing to parse, or if the parse is not successful

parse :: Parser s a -> Text -> Either Text a Source #

Shortcut for parsing some text by splitting it on spaces

parserOf :: forall a b. (ApplyVariadic (Parser Command) a b, Typeable a, Typeable b) => a -> Typed b Source #

Create a Parser a for a given constructor of type a by using the Applicative instance of a Parser

maybeParser :: Parser s a -> Parser s (Maybe a) Source #

Make a Parser for a Maybe type. If the original parser does not succeeds this parser returns Nothing and does not consume anything

listParser :: Parser s a -> Parser s [a] Source #

Make a Parser for a List type. This works by repeatedly applying the original parser to inputs (and appending results) until the parser fails in which case [] is returned

list1Parser :: Parser s a -> Parser s [a] Source #

Make a Parser for a List type where at least one value is expected to be parsed

nonEmptyParser :: Parser s a -> Parser s (NonEmpty a) Source #

Make a Parser for a NonEmpty type (this means that least one value is expected to be parsed)

parseField :: forall s a. (KnownSymbol s, Typeable a, Show a) => FieldConfiguration -> Positional -> Text -> OptionDescriptionUpdates -> DefaultValue s a -> ActiveValue s a -> Decoder a -> Parser s a Source #

Create a Parser for command-line field given: - fieldOptions to derive longshortmetavar names from a field name - a field name. If it is missing, then we can only parse arguments - a field type. We use the type to make a METAVAR - additional OptionDescription to either override the previous values, or to add the field help - an optional default value for the field: the value to use if the field is missing - an optional active value for the field: the value to use if the field is present - a Decoder to read the value as text

parseWith :: forall s a. (KnownSymbol s, Typeable a, Show a) => OptionDescriptionUpdates -> DefaultValue s a -> ActiveValue s a -> Decoder a -> Parser s a Source #

Create a parser for a given field given: - its name(s) - an optional default value for the field: the value to use if the field is missing - an optional active value for the field: the value to use if the field is present - a Decoder to read the value as text

takeOptionValue :: [Text] -> Lexemes -> Maybe (Text, Maybe Text, Lexemes) Source #

Find a value for a given option name return Nothing if the name is not found If the name is found return - Nothing if there is no value - the first value for that name if there is is one and remove the value associated to the flag if there aren't any values left associated to a flag, remove it

takeArgumentValue :: Lexemes -> Maybe (Text, Lexemes) Source #

Take the first argument value available and remove it from the list of lexed arguments

getSymbol :: forall s. KnownSymbol s => Text Source #

Return the textual representation of a symbol (this is a fully qualified string)

showType :: forall a. Typeable a => Text Source #

Return the type of a value as Text