flatparse-0.5.1.0: High-performance parsing from strict bytestrings
Safe HaskellSafe-Inferred
LanguageHaskell2010

FlatParse.Stateful.Base

Description

Basic parser building blocks.

Synopsis

Bytewise

eof :: ParserT st r e () Source #

Succeed if the input is empty.

take :: Int -> ParserT st r e ByteString Source #

Read n bytes as a ByteString. Fails if fewer than n bytes are available.

Throws a runtime error if given a negative integer.

This does no copying. The ByteString returned is a "slice" of the input, and will keep it alive. To avoid this, use copy on the output.

take# :: Int# -> ParserT st r e ByteString Source #

Read n# bytes as a ByteString. Fails if fewer than n# bytes are available.

Throws a runtime error if given a negative integer.

This does no copying. The ByteString returned is a "slice" of the input, and will keep it alive. To avoid this, use copy on the output.

takeUnsafe# :: Int# -> ParserT st r e ByteString Source #

Read i# bytes as a ByteString. Fails if newer than i# bytes are available.

Undefined behaviour if given a negative integer.

This does no copying. The ByteString returned is a "slice" of the input, and will keep it alive. To avoid this, use copy on the output.

takeRest :: ParserT st r e ByteString Source #

Consume the rest of the input. May return the empty bytestring.

This does no copying. The ByteString returned is a "slice" of the input, and will keep it alive. To avoid this, use copy on the output.

skip :: Int -> ParserT st r e () Source #

Skip forward n bytes. Fails if fewer than n bytes are available.

Throws a runtime error if given a negative integer.

skip# :: Int# -> ParserT st r e () Source #

Skip forward n bytes. Fails if fewer than n bytes are available.

Throws a runtime error if given a negative integer.

skipBack :: Int -> ParserT st r e () Source #

Go back i bytes in the input. Takes a positive integer.

Extremely unsafe. Makes no checks. Almost certainly a Bad Idea.

skipBack# :: Int# -> ParserT st r e () Source #

Go back i# bytes in the input. Takes a positive integer.

Extremely unsafe. Makes no checks. Almost certainly a Bad Idea.

atSkip# :: Int# -> ParserT st r e ret -> ParserT st r e ret Source #

Skip forward n# bytes and run the given parser. Fails if fewer than n# bytes are available.

Throws a runtime error if given a negative integer.

atSkipUnsafe# :: Int# -> ParserT st r e ret -> ParserT st r e ret Source #

Skip forward i# bytes and run the given parser. Fails if fewer than i bytes are available.

Undefined behaviour if given a negative integer.

Combinators

branch :: ParserT st r e a -> ParserT st r e b -> ParserT st r e b -> ParserT st r e b Source #

Branch on a parser: if the first argument succeeds, continue with the second, else with the third. This can produce slightly more efficient code than (<|>). Moreover, ḃranch does not backtrack from the true/false cases.

notFollowedBy :: ParserT st r e a -> ParserT st r e b -> ParserT st r e a Source #

Succeed if the first parser succeeds and the second one fails.

chainl :: (b -> a -> b) -> ParserT st r e b -> ParserT st r e a -> ParserT st r e b Source #

An analogue of the list foldl function: first parse a b, then parse zero or more a-s, and combine the results in a left-nested way by the b -> a -> b function. Note: this is not the usual chainl function from the parsec libraries!

chainr :: (a -> b -> b) -> ParserT st r e a -> ParserT st r e b -> ParserT st r e b Source #

An analogue of the list foldr function: parse zero or more a-s, terminated by a b, and combine the results in a right-nested way using the a -> b -> b function. Note: this is not the usual chainr function from the parsec libraries!

lookahead :: ParserT st r e a -> ParserT st r e a Source #

Save the parsing state, then run a parser, then restore the state.

ensure :: Int -> ParserT st r e () Source #

Assert that there are at least n bytes remaining.

Undefined behaviour if given a negative integer.

ensure# :: Int# -> ParserT st r e () Source #

Assert that there are at least n# bytes remaining.

Undefined behaviour if given a negative integer.

withEnsure :: Int -> ParserT st r e ret -> ParserT st r e ret Source #

Assert that there are at least n# bytes remaining (CPS).

Undefined behaviour if given a negative integer.

withEnsure1 :: ParserT st r e ret -> ParserT st r e ret Source #

Assert that there is at least 1 byte remaining (CPS).

Undefined behaviour if given a negative integer.

withEnsure# :: Int# -> ParserT st r e ret -> ParserT st r e ret Source #

Assert that there are at least n# bytes remaining (CPS).

Undefined behaviour if given a negative integer.

isolate :: Int -> ParserT st r e a -> ParserT st r e a Source #

isolate n p runs the parser p isolated to the next n bytes. All isolated bytes must be consumed.

Throws a runtime error if given a negative integer.

isolate# :: Int# -> ParserT st r e a -> ParserT st r e a Source #

isolate# n# p runs the parser p isolated to the next n# bytes. All isolated bytes must be consumed.

Throws a runtime error if given a negative integer.

isolateUnsafe# :: Int# -> ParserT st r e ret -> ParserT st r e ret Source #

isolateUnsafe# i# p runs the parser p isolated to the next i# bytes. All isolated bytes must be consumed.

Undefined behaviour if given a negative integer.

Non-specific (TODO)

skipMany :: ParserT st r e a -> ParserT st r e () Source #

Skip a parser zero or more times.

skipSome :: ParserT st r e a -> ParserT st r e () Source #

Skip a parser one or more times.

Errors and failures

failed :: ParserT st r e a Source #

The failing parser. By default, parser choice (<|>) arbitrarily backtracks on parser failure. This is a synonym for empty.

try :: ParserT st r e a -> ParserT st r e a Source #

Convert a parsing error into failure.

err :: e -> ParserT st r e a Source #

Throw a parsing error. By default, parser choice (<|>) can't backtrack on parser error. Use try to convert an error to a recoverable failure.

withError :: ParserT st r e b -> (e -> ParserT st r e b) -> ParserT st r e b Source #

Run the parser, if an error is thrown, handle it with the given function.

fails :: ParserT st r e a -> ParserT st r e () Source #

Convert a parsing failure to a success.

cut :: ParserT st r e a -> e -> ParserT st r e a Source #

Convert a parsing failure to an error.

cutting :: ParserT st r e a -> e -> (e -> e -> e) -> ParserT st r e a Source #

Run the parser, if we get a failure, throw the given error, but if we get an error, merge the inner and the newly given errors using the e -> e -> e function. This can be useful for implementing parsing errors which may propagate hints or accummulate contextual information.

optional :: ParserT st r e a -> ParserT st r e (Maybe a) Source #

Convert a parsing failure to a Maybe. If possible, use withOption instead.

optional_ :: ParserT st r e a -> ParserT st r e () Source #

Convert a parsing failure to a ().

withOption :: ParserT st r e a -> (a -> ParserT st r e ret) -> ParserT st r e ret -> ParserT st r e ret Source #

CPS'd version of optional. This is usually more efficient, since it gets rid of the extra Maybe allocation.