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

Data.Registry.Options.Lexemes

Description

This module parses strings coming from the command line and tries to classify them as:

  • option names + their associated values
  • flag names
  • arguments

It is however not always possible to know if a given list of string is:

  • an option name + some values: find --files file1 file2
  • a flag name + some arguments: copy --force source target

During lexing we leave this last case as "ambiguous". This will be disambiguated during parsing where we know if a given name is an option or a flag.

Synopsis

Documentation

data Lexemes Source #

This data type helps pre-parsing option names and values

Constructors

Lexemes 

Fields

Instances

Instances details
Monoid Lexemes Source # 
Instance details

Defined in Data.Registry.Options.Lexemes

Semigroup Lexemes Source # 
Instance details

Defined in Data.Registry.Options.Lexemes

Show Lexemes Source # 
Instance details

Defined in Data.Registry.Options.Lexemes

Eq Lexemes Source # 
Instance details

Defined in Data.Registry.Options.Lexemes

Methods

(==) :: Lexemes -> Lexemes -> Bool #

(/=) :: Lexemes -> Lexemes -> Bool #

union :: Lexemes -> Lexemes -> Lexemes Source #

Concatenate 2 lists of lexemes

override :: Lexemes -> Lexemes -> Lexemes Source #

Override the values from one Lexemes with the values from another This is a bit tricky since ambiguous option/flags coming from the command can eventually be detected to be valid options / flags when parsed as such in the environment or in a config file

Create lexemes

lexArgs :: [Text] -> Lexemes Source #

Lex some input arguments They are first stripped of additional whitespace and empty strings are removed (there shouldn't be any though, coming from the command line)

mkLexemes :: [Text] -> Lexemes Source #

Lex some input arguments

optionLexemes :: Text -> Text -> Lexemes Source #

Create lexemes for an option name + an option value

optionsLexemes :: Text -> [Text] -> Lexemes Source #

Create lexemes for an option name + a list of option values

makeEqualOptionLexeme :: Text -> Lexemes Source #

Create an option for --option=value or -o=value Return mempty if no equal sign is present

makeFlagsLexeme :: Text -> Lexemes Source #

Create lexemes for a list of potentially short flag names e.g. makeFlagsLexeme "-opq" === flagsLexemes ["o", "p", "q"]

flagLexemes :: Text -> Lexemes Source #

Create lexemes for a flag name

flagsLexemes :: [Text] -> Lexemes Source #

Create lexemes for a list of flag names

argLexemes :: Text -> Lexemes Source #

Create lexemes for an argument value

argsLexemes :: [Text] -> Lexemes Source #

Create lexemes for several arguments

ambiguousLexemes :: Text -> [Text] -> Lexemes Source #

Create lexemes an ambiguous flag an its values Later parsing will indicate if the name is an option names and the values the option values or if this is a flag + arguments

getArguments :: Lexemes -> [Text] Source #

Return the possible list of argument values to parse from Note that there can be ambiguous flags

getFlagNames :: Lexemes -> [Text] Source #

Return option/flag names from lexed values

getValue :: Text -> Lexemes -> Maybe (Maybe Text) Source #

Return a value for a given name This can be a value associated to a given option or just a flag name acting as a value to decode (the value can also come from an ambiguous option value)

popOptionValue :: Text -> Lexemes -> Lexemes Source #

Remove the value associated to an option name The value might be: - associated to an option name - the name of a flag - associated to an ambiguous flag name

popArgumentValue :: Lexemes -> Lexemes Source #

Remove an argument value first from the list of arguments if there are some` otherwise remove a value in the list of values associated to an ambiguous flag

popFlag :: Text -> Lexemes -> Lexemes Source #

Remove a flag If the flag is actually an ambiguous flag with some associated values then this means that those values were arguments and need to be treated as such

isDashed :: Text -> Bool Source #

Return True if some text starts with -

isSingleDashed :: Text -> Bool Source #

Return True if some text starts with - but not with `--`

dropDashed :: Text -> Text Source #

Drop dashes in front of a flag name

MultiMap functions

pop :: Ord k => k -> MultiMap k v -> MultiMap k v Source #

Drop the first value associated to a key in the map If a key has no more values drop the key

Orphan instances

(Show k, Show v) => Show (MultiMap k v) Source # 
Instance details

Methods

showsPrec :: Int -> MultiMap k v -> ShowS #

show :: MultiMap k v -> String #

showList :: [MultiMap k v] -> ShowS #

(Eq k, Eq v) => Eq (MultiMap k v) Source # 
Instance details

Methods

(==) :: MultiMap k v -> MultiMap k v -> Bool #

(/=) :: MultiMap k v -> MultiMap k v -> Bool #