multiarg-0.2.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.

Synopsis

Parser types

type Parser a = ParserT () SimpleError Identity aSource

Parser a is a parser with user state (), error type SimpleError, underlying monad Identity, and result type a.

type ParserE e a = ParserT () e Identity aSource

ParserE e a is a parser with user state (), error type e, underlying monad Identity, and result type a.

type ParserSE s e a = ParserT s e Identity aSource

ParserSE s e a is a parser with user state s, error type e, underlying monad Identity, and result type a.

data ParserT s e m a Source

ParserT s e m a is a parser with user state s, error type e, underlying monad m, and result type a. Internally the parser is a state monad which keeps track of what is remaining to be parsed. Since the parser has an internal state anyway, the user can add to this state (this is called the user state.) The parser ignores this user state so you can use it however you wish. If you do not need a user state, just make it the unit type ().

The parser also includes the notion of failure. Any parser can fail; a failed parser affects the behavior of combinators such as combine. The failure type should be a instance of System.Console.MultiArg.Error.Error. This allows you to define your own type and use it for the failure type, which can be useful when combining MultiArg with your own program.

The underlying monad is m. This makes ParserT into a monad transformer; you can layer it on top of other monads. For instance you might layer it on top of the IO monad so that your parser can perform IO (for example, by examining the disk to see if arguments that specify files are valid.) If you don't need a monad transformer, just layer ParserT on top of Identity.

Instances

MonadTrans (ParserT s e) 
(Error e, Monad m) => Monad (ParserT s e m) 
Monad m => Functor (ParserT s e m) 
(Monad m, Error e) => MonadPlus (ParserT s e m) 
Monad m => Applicative (ParserT s e m) 
(Monad m, Error e) => Alternative (ParserT s e m) 
(MonadIO m, Error e) => MonadIO (ParserT s e m) 
(Monad m, Error e) => Monoid (ParserT s e m a) 

Running a parser

Each parser runner is applied to a list of Text, which are the command line arguments to parse. If there is any chance that you will be parsing Unicode strings, see the documentation in GetArgs before you use getArgs.

parseSource

Arguments

:: [Text]

Command line arguments to parse

-> Parser a

Parser to run

-> Exceptional SimpleError a

Successful result or an error

The simplest parser runner; has no user state, an underlying monad Identity, and error type SimpleError.

parseESource

Arguments

:: [Text]

Command line arguments to parse

-> ParserE e a

Parser to run

-> Exceptional e a

Success or failure

Runs a parser that has no user state and an underlying monad of Identity and is parameterized on the error type.

parseSESource

Arguments

:: s

The initial user state

-> [Text]

Command line arguments

-> ParserSE s e a

Parser to run

-> (Exceptional e a, s)

Success or failure, and the final user state

Runs a parser that has a user state and an underlying monad Identity.

parseTSource

Arguments

:: Monad m 
=> s

Initial user state

-> [Text]

Command line arguments to parse

-> ParserT s e m a

Parser to run

-> m (Exceptional e a, s)

Success or failure and the final user state, inside of the underlying monad

The most complex parser runner. Runs a parser with a user-defined state, error type, and underlying monad. Returns the final parse result and the final user state, inside of the underlying monad.

Higher-level parser combinators

parserMap :: Monad m => (a -> b) -> ParserT s e m a -> ParserT s e m 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 :: Monad m => a -> ParserT s e m aSource

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

apply :: Monad m => ParserT s e m (a -> b) -> ParserT s e m a -> ParserT s e m 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 :: Monad m => ParserT s e m a -> ParserT s e m a -> ParserT s e m 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 :: Monad m => ParserT s e m a -> (a -> ParserT s e m b) -> ParserT s e m 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 :: Monad m => ParserT s e m a -> ParserT s e m 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 :: Monad m => ParserT s e m a -> ParserT s e m [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 :: Monad m => ParserT s e m a -> ParserT s e m end -> ParserT s e m [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.

feed :: Monad m => (a -> ParserT s e m a) -> (a -> ParserT s e m end) -> a -> ParserT s e m [a]Source

feed runs in a recursive loop. Each loop starts with three variables: a function f that takes an input i and returns a parser p, a function g that takes an input i and returns a parser e that must succeed for the recursion to end, and an initial input i. This proceeds as follows:

  1. Apply g to i and run resulting parser e. If this parser succeeds, feed succeeds and returns a list of all successful runs of p. The result of e is not returned, but otherwise the parser returned reflects the updated internal parser state from the running of e. (If that is a problem, wrap e in lookAhead.) If e fails and consumes input, feed fails and returns a failed parser whose internal state reflects the state after e fails. If e fails without consuming any input, proceed with the following steps.
  2. Apply function f to input i, yielding a parser p. Run parser p. If p fails, feed also fails. If p succeeds, it yields a new input, i'.
  3. If p succeeded without consuming any input, an infinite loop will result, so apply error.
  4. Repeat from step 1, but with the new input retured from p, i'.

For the initial application of feed, you supply the function f, the end parser e, and the initial state i.

This function is useful for running multiple times a parser that depends on the result of previous runs of the parser. You could implement something similar using the user state feature, but for various reasons sometimes it is more useful to use feed instead.

Monad lifting

parserLift :: Monad m => m a -> ParserT s e m aSource

Lifts a computation of the underlying monad into the ParserT monad. This provides the implementation for lift.

parserIO :: (MonadIO m, Error e) => IO a -> ParserT s e m aSource

Lifts a computation from the IO monad into the ParserT monad. This provides the implementation for liftIO.

Failure and errors

throw :: Monad m => e -> ParserT s e m aSource

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

throwString :: (Error e, Monad m) => String -> ParserT s e m 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 :: (Monad m, Error e) => ParserT s e m aSource

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

(<?>) :: Monad m => ParserT s e m a -> e -> ParserT s e m aSource

Runs the parser given. If it succeeds, then returns the result of the parser. If it fails and consumes input, returns the result of the parser. If it fails without consuming any input, then changes the error using the function given.

try :: Monad m => ParserT s e m a -> ParserT s e m aSource

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

Parsers

Short options and arguments

pendingShortOpt :: (Monad m, Error e) => ShortOpt -> ParserT s e m ShortOptSource

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; returns the short option parsed.

nonPendingShortOpt :: (Error e, Monad m) => ShortOpt -> ParserT s e m ShortOptSource

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. Returns the short option parsed.

pendingShortOptArg :: (Error e, Monad m) => ParserT s e m TextSource

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 text of the pending short option argument (this text cannot be empty).

Long options and arguments

exactLongOpt :: (Error e, Monad m) => LongOpt -> ParserT s e m (LongOpt, Maybe Text)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 :: (Error e, Monad m) => Set LongOpt -> ParserT s e m (Text, LongOpt, Maybe Text)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.

Stoppers

stopper :: (Error e, Monad m) => ParserT s e m ()Source

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

Positional (non-option) arguments

nextArg :: (Error e, Monad m) => ParserT s e m TextSource

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 :: (Error e, Monad m) => ParserT s e m TextSource

Returns the next string on the command line as long as there are no pendings and as long as the next string does not begin with a dash. If there has already been a stopper, then will return the next string even if it starts with a dash.

Miscellaneous

end :: (Error e, Monad m) => ParserT s e m ()Source

Succeeds if there is no more input left.

User state

get :: Monad m => ParserT s e m sSource

Gets the user state.

put :: Monad m => s -> ParserT s e m ()Source

Puts a new user state.

modify :: Monad m => (s -> s) -> ParserT s e m ()Source

Modify the user state.