multiarg-0.4.0.0: Combinators to build command line parsers

Safe HaskellSafe-Infered

System.Console.MultiArg.Prim

Contents

Description

Parser primitives. These are the only functions that have access to the internals of the parser. Use these functions if you want to build your own parser from scratch. If your needs are simpler, you will want to look at System.Console.MultiArg.SimpleParser or System.Console.MultiArg.Combinator, which do a lot of grunt work for you.

Synopsis

Parser types

data Parser a Source

Parsers. Internally the parser tracks what input remains to be parsed, whether there are any pending short options, and whether a stopper has been seen. A parser can return a value of any type.

The parser also includes the notion of failure. Any parser can fail; a failed parser affects the behavior of combinators such as combine.

Running a parser

Each parser runner is applied to a list of Strings, which are the command line arguments to parse.

parseSource

Arguments

:: [String]

Command line arguments to parse. Presumably you got these from getArgs. If there is any chance that you will be parsing Unicode strings, see the documentation in System.Console.MultiArg.GetArgs before you use getArgs.

-> Parser a

Parser to run

-> Exceptional Error a

Success or failure. Any parser might fail; for example, the command line might not have any values left to parse. Use of the choice combinator can lead to a list of failures. If multiple parsers are tried one after another using the choice combinator, and each fails without consuming any input, then multiple Error will result, one for each failure.

Runs a parser. This is the only way to change a value of type Parser a into a value of type a (that is, it is the only way to "get out of the Parser monad" or to "escape the Parser monad".)

Higher-level parser combinators

parserMap :: (a -> b) -> Parser a -> Parser bSource

parserMap f p applies function f to the result of parser p. First parser p is run. If it succeeds, function f is applied to the result and another parser is returned with the result. If it fails, f is not applied and a failed parser is returned. This provides the implementation for fmap.

good :: a -> Parser aSource

good a always succeeds without consuming any input and has result a. This provides the implementation for return and pure.

apply :: Parser (a -> b) -> Parser a -> Parser bSource

apply l r applies the function found in parser l to the result of parser r. First the l parser is run. If it succeeds, it has a resulting function. Then the r parser is run. If it succeeds, the function from the l parser is applied to the result of the r parser, and a new parser is returned with the result. If either parser l or parser r fails, then a failed parser is returned. This provides the implementation for <*> in Applicative.

choice :: Parser a -> Parser a -> Parser aSource

Runs the first parser. If it fails without consuming any input, then runs the second parser. If the first parser succeeds, then returns the result of the first parser. If the first parser fails and consumes input, then returns the result of the first parser. This provides the implementation for <|> in Alternative.

combine :: Parser a -> (a -> Parser b) -> Parser bSource

Combines two parsers into a single parser. The second parser can optionally depend upon the result from the first parser.

This applies the first parser. If the first parser succeeds, combine then takes the result from the first parser, applies the function given to the result from the first parser, and then applies the resulting parser.

If the first parser fails, combine will not apply the second function but instead will bypass the second parser.

This provides the implementation for >>= in Monad.

lookAhead :: Parser a -> Parser aSource

lookAhead p runs parser p. If p succeeds, lookAhead p succeeds without consuming any input. If p fails without consuming any input, so does lookAhead. If p fails and consumes input, lookAhead also fails and consumes input. If this is undesirable, combine with try.

Running parsers multiple times

several :: Parser a -> Parser [a]Source

several p runs parser p zero or more times and returns all the results. This proceeds like this: parser p is run and, if it succeeds, the result is saved and parser p is run again. Repeat. Eventually this will have to fail. If the last run of parser p fails without consuming any input, then several p runs successfully. The state of the parser is updated to reflect the successful runs of p. If the last run of parser p fails but it consumed input, then several p fails. The state of the parser is updated to reflect the state up to and including the run that partially consumed input. The parser is left in a failed state.

This semantic can come in handy. For example you might run a parser multiple times that parses an option and arguments to the option. If the arguments fail to parse, then several will fail.

This function provides the implementation for many.

manyTill :: Parser a -> Parser end -> Parser [a]Source

manyTill p e runs parser p repeatedly until parser e succeeds.

More precisely, first it runs parser e. If parser e succeeds, then manyTill returns the result of all the preceding successful parses of p. If parser e fails (it does not matter whether e consumed any input or not), manyTill runs parser p again. What happens next depends on whether p succeeded or failed. If p succeeded, then the loop starts over by running parser e again. If p failed (it does not matter whether it consumed any input or not), then manyTill fails. The state of the parser is updated to reflect its state after the failed run of p, and the parser is left in a failed state.

Should parser e succeed (as it will on a successful application of manyTill), then the parser state will reflect that parser e succeeded--that is, if parser e consumes input, that input will be consumed in the parser that is returned. Wrap e inside of lookAhead if that is undesirable.

Be particularly careful to get the order of the arguments correct. Applying this function to reversed arguments will yield bugs that are very difficult to diagnose.

Failure and errors

throw :: Message -> Parser aSource

throw e always fails without consuming any input and returns a failed parser with error state e.

throwString :: String -> Parser aSource

throwString s always fails without consuming any input. The failure contains a record of the string passed in by s. This provides the implementation for fail.

genericThrow :: Parser aSource

Fail with an unhelpful error message. Usually throw is more useful, but this is handy to implement some typeclass instances.

(<??>) :: Parser a -> ([Message] -> [Message]) -> Parser aSource

Runs the parser given. If it fails without consuming any input, then applies the given function to the list of messages and replaces the list of messages with the list returned by the function. Otherwise, returns the result of the parser.

try :: Parser a -> Parser aSource

try p behaves just like p, but if p fails, try p will not consume any input.

Parsers

Short options and arguments

pendingShortOpt :: ShortOpt -> Parser ()Source

Parses only pending short options. Fails without consuming any input if there has already been a stopper or if there are no pending short options. Fails without consuming any input if there is a pending short option, but it does not match the short option given. Succeeds and consumes a pending short option if it matches the short option given.

nonPendingShortOpt :: ShortOpt -> Parser ()Source

Parses only non-pending short options. Fails without consuming any input if, in order:

  • there are pending short options
  • there has already been a stopper
  • there are no arguments left to parse
  • the next argument is an empty string
  • the next argument does not begin with a dash
  • the next argument is a single dash
  • the next argument is a short option but it does not match the one given
  • the next argument is a stopper

Otherwise, consumes the next argument, puts any remaining letters from the argument into a pending short, and removes the first word from remaining arguments to be parsed.

pendingShortOptArg :: Parser StringSource

Parses only pending short option arguments. For example, for the tail command, if you enter the option -c25, then after parsing the -c option the 25 becomes a pending short option argument because it was in the same command line argument as the -c.

Fails without consuming any input if:

  • a stopper has already been parsed
  • there are no pending short option arguments

On success, returns the String of the pending short option argument (this String will never be empty).

Long options and arguments

exactLongOpt :: LongOpt -> Parser (Maybe String)Source

Parses an exact long option. That is, the text of the command-line option must exactly match the text of the option. Returns the option, and any argument that is attached to the same word of the option with an equal sign (for example, --follow=/dev/random will return Just "/dev/random" for the argument.) If there is no equal sign, returns Nothing for the argument. If there is an equal sign but there is nothing after it, returns Just "" for the argument.

If you do not want your long option to have equal signs and GNU-style option arguments, wrap this parser in something that will fail if there is an option argument.

Fails without consuming any input if:

  • there are pending short options
  • a stopper has been parsed
  • there are no arguments left on the command line
  • the next argument on the command line does not begin with two dashes
  • the next argument on the command line is -- (a stopper)
  • the next argument on the command line does begin with two dashes but its text does not match the argument we're looking for

approxLongOpt :: Set LongOpt -> Parser (String, LongOpt, Maybe String)Source

Examines the next word. If it matches a Text in the set unambiguously, returns a tuple of the word actually found and the matching word in the set and the accompanying text after the equal sign (if any). If the Set is empty, this parser will always fail.

Stoppers

stopper :: Parser ()Source

Parses a "stopper" - that is, a double dash. Changes the internal state of the parser to reflect that a stopper has been seen.

resetStopper :: Parser ()Source

If a stopper has already been seen, change the internal state back to indicating that no stopper has been seen.

Positional (non-option) arguments

nextArg :: Parser StringSource

Returns the next string on the command line as long as there are no pendings. Be careful - this will return the next string even if it looks like an option (that is, it starts with a dash.) Consider whether you should be using nonOptionPosArg instead. However this can be useful when parsing command line options after a stopper.

nonOptionPosArg :: Parser StringSource

If there are pending short options, fails without consuming any input.

Otherwise, if a stopper has NOT already been parsed, then returns the next word if it is either a single dash or any other word that does not begin with a dash. If the next word does not meet these criteria, fails without consuming any input.

Otherwise, if a stopper has already been parsed, then returns the next word, regardless of whether it begins with a dash or not.

Miscellaneous

end :: Parser ()Source

Succeeds if there is no more input left.

Errors

data Message Source

Error messages.

Constructors

Expected String

The parser expected to see one thing, but it actually saw something else. The string indicates what was expected.

StrMsg String

The fromString function was applied.

Replaced String

A previous list of error messages was replaced with this error message.

UnknownError

Any other error; used by genericThrow.

Instances

data Error Source

An Error contains a list of Messages and a String indicating where the error happened.

Constructors

Error [Message] Location 

Instances