attoparsec-text-0.8.5.2: Fast combinator parsing for texts

Portabilityunknown
Stabilityexperimental
Maintainerfelipe.lessa@gmail.com

Data.Attoparsec.Text

Contents

Description

Simple, efficient combinator parsing for Text strings, loosely based on the Parsec library.

Synopsis

Differences from Parsec

Compared to Parsec 3, attoparsec-text makes several tradeoffs. It is not intended for, or ideal for, all possible uses.

  • While attoparsec-text can consume input incrementally, Parsec cannot. Incremental input is a huge deal for efficient and secure network and system programming, since it gives much more control to users of the library over matters such as resource usage and the I/O model to use.
  • Much of the performance advantage of attoparsec-text is gained via high-performance parsers such as takeWhile and string. If you use complicated combinators that return lists of characters, there is less performance difference between the two libraries.
  • Unlike Parsec 3, attoparsec-text does not support being used as a monad transformer.
  • attoparsec-text is specialised to deal only with strict Text input. Efficiency concernts rule out both lists and lazy texts. The usual use for lazy texts would be to allow consumption of very large input without a large footprint. For this need, attoparsec-text's incremental input provides an excellent substitute, with much more control over when input takes place. If you must use lazy texts, see the Lazy module, which feeds lazy chunks to a regular parser.
  • Parsec parsers can produce more helpful error messages than attoparsec-text parsers. This is a matter of focus: attoparsec-text avoids the extra book-keeping in favour of higher performance.

Incremental input

attoparsec-text supports incremental input, meaning that you can feed it a text that represents only part of the expected total amount of data to parse. If your parser reaches the end of a fragment of input and could consume more input, it will suspend parsing and return a Partial continuation.

Supplying the Partial continuation with another text will resume parsing at the point where it was suspended. You must be prepared for the result of the resumed parse to be another Partial continuation.

To indicate that you have no more input, supply the Partial continuation with an empty text.

Remember that some parsing combinators will not return a result until they reach the end of input. They may thus cause Partial results to be returned.

If you do not need support for incremental input, consider using the parseOnly function to run your parser. It will never prompt for more input.

Performance considerations

To actually achieve high performance, there are a few guidelines that it is useful to follow.

Use the Text-oriented parsers whenever possible, e.g. takeWhile1 instead of many1 anyChar. There is about a factor of 100 difference in performance between the two kinds of parser.

For very simple character-testing predicates, write them by hand instead of using inClass or notInClass. For instance, both of these predicates test for an end-of-line character, but the first is much faster than the second:

endOfLine_fast c = w == '\r' || c == '\n'
endOfLine_slow   = inClass "\r\n"

Make active use of benchmarking and profiling tools to measure, find the problems with, and improve the performance of your parser.

Parser types

data Result r Source

The result of a parse.

Constructors

Fail Text [String] String

The parse failed. The Text is the input that had not yet been consumed when the failure occurred. The [String] is a list of contexts in which the error occurred. The String is the message describing the error, if any.

Partial (Text -> Result r)

Supply this continuation with more input so that the parser can resume. To indicate that no more input is available, use an empty string.

Done Text r

The parse succeeded. The Text is the input that had not yet been consumed (if any) when the parse succeeded.

Instances

Typeclass instances

The Parser type is an instance of the following classes:

  • Monad, where fail throws an exception (i.e. fails) with an error message.
  • Functor and Applicative, which follow the usual definitions.
  • MonadPlus, where mzero fails (with no error message) and mplus executes the right-hand parser if the left-hand one fails.
  • Alternative, which follows MonadPlus.

The Result type is an instance of Functor, where fmap transforms the value in a Done result.

Running parsers

parse :: Parser a -> Text -> Result aSource

Run a parser.

feed :: Result r -> Text -> Result rSource

If a parser has returned a Partial result, supply it with more input.

parseOnly :: Parser a -> Text -> Either String aSource

Run a parser that cannot be resupplied via a Partial result.

parseWithSource

Arguments

:: Monad m 
=> m Text

An action that will be executed to provide the parser with more input, if necessary. The action must return an empty string when there is no more input available.

-> Parser a 
-> Text

Initial input for the parser.

-> m (Result a) 

Run a parser with an initial input string, and a monadic action that can supply more input if needed.

parseTest :: Show a => Parser a -> Text -> IO ()Source

Run a parser and print its result to standard output.

Result conversion

maybeResult :: Result r -> Maybe rSource

Convert a Result value to a Maybe value. A Partial result is treated as failure.

eitherResult :: Result r -> Either String rSource

Convert a Result value to an Either value. A Partial result is treated as failure.

Combinators

(<?>)Source

Arguments

:: Parser a 
-> String

the name to use if parsing fails

-> Parser a 

try :: Parser a -> Parser aSource

Attempt a parse, and if it fails, rewind the input so that no input appears to have been consumed.

This combinator is useful in cases where a parser might consume some input before failing, i.e. the parser needs arbitrary lookahead. The downside to using this combinator is that it can retain input for longer than is desirable.

Parsing individual characters

char :: Char -> Parser CharSource

Match a specific character.

anyChar :: Parser CharSource

Match any character.

notChar :: Char -> Parser CharSource

Match any character except the given one.

satisfy :: (Char -> Bool) -> Parser CharSource

The parser satisfy p succeeds for any character for which the predicate p returns True. Returns the character that is actually parsed.

import Data.Char (isDigit)
digit = satisfy isDigit

satisfyWith :: (Char -> a) -> (a -> Bool) -> Parser aSource

The parser satisfyWith f p transforms a character, and succeeds if the predicate p returns True on the transformed value. The parser returns the transformed character that was parsed.

skip :: (Char -> Bool) -> Parser ()Source

The parser skip p succeeds for any character for which the predicate p returns True.

import Data.Char (isDigit)
digit = satisfy isDigit

Special character parsers

Special parser for characters. Unlike the original attoparsec package, these parsers do work correctly for all encodings. Internally Data.Char module is used.

digit :: Parser CharSource

Parse a single digit.

letter :: Parser CharSource

Parse a single letter.

space :: Parser CharSource

Parse a space character.

Character classes

inClass :: String -> Char -> BoolSource

Match any character in a set.

vowel = inClass "aeiou"

Range notation is supported.

halfAlphabet = inClass "a-nA-N"

To add a literal '-' to a set, place it at the beginning or end of the string.

notInClass :: String -> Char -> BoolSource

Match any character not in a set.

Efficient string handling

string :: Text -> Parser TextSource

string s parses a sequence of characters that identically match s. Returns the parsed string (i.e. s). This parser consumes no input if it fails (even if a partial match).

Note: The behaviour of this parser is different to that of the similarly-named parser in Parsec, as this one is all-or-nothing. To illustrate the difference, the following parser will fail under Parsec given an input of for:

string "foo" <|> string "for"

The reason for its failure is that that the first branch is a partial match, and will consume the letters 'f' and 'o' before failing. In Attoparsec, both the original on bytestrings and this one on texts, the above parser will succeed on that input, because the failed first branch will consume nothing.

skipSpace :: Parser ()Source

Skip over white space.

skipWhile :: (Char -> Bool) -> Parser ()Source

Skip past input for as long as the predicate returns True.

take :: Int -> Parser TextSource

Consume exactly n characters of input.

scan :: s -> (s -> Char -> Maybe s) -> Parser TextSource

A stateful scanner. The predicate consumes and transforms a state argument, and each transformed state is passed to successive invocations of the predicate on each character of the input until one returns Nothing or the input ends.

This parser does not fail. It will return an empty string if the predicate returns Nothing on the first character of input.

Note: Because this parser does not fail, do not use it with combinators such as many, because such parsers loop until a failure occurs. Careless use will thus result in an infinite loop.

takeWhile :: (Char -> Bool) -> Parser TextSource

Consume input as long as the predicate returns True, and return the consumed input.

This parser does not fail. It will return an empty string if the predicate returns False on the first character of input.

Note: Because this parser does not fail, do not use it with combinators such as many, because such parsers loop until a failure occurs. Careless use will thus result in an infinite loop.

takeWhile1 :: (Char -> Bool) -> Parser TextSource

Consume input as long as the predicate returns True, and return the consumed input.

This parser requires the predicate to succeed on at least one character of input: it will fail if the predicate never returns True or if there is no input left.

takeTill :: (Char -> Bool) -> Parser TextSource

Consume input as long as the predicate returns False (i.e. until it returns True), and return the consumed input.

This parser does not fail. It will return an empty string if the predicate returns True on the first character of input.

Note: Because this parser does not fail, do not use it with combinators such as many, because such parsers loop until a failure occurs. Careless use will thus result in an infinite loop.

Consume all remaining input

takeText :: Parser TextSource

Consume all remaining input and return it as a single string.

takeLazyText :: Parser TextSource

Consume all remaining input and return it as a single string.

Text parsing

endOfLine :: Parser ()Source

Match either a single newline character '\n', or a carriage return followed by a newline character "\r\n".

Numeric parsers

decimal :: Integral a => Parser aSource

Parse and decode an unsigned decimal number.

hexadecimal :: Integral a => Parser aSource

Parse and decode an unsigned hexadecimal number. The hex digits 'a' through 'f' may be upper or lower case.

This parser does not accept a leading "0x" string.

signed :: Num a => Parser a -> Parser aSource

Parse a number with an optional leading '+' or '-' sign character.

double :: Parser DoubleSource

Parse a rational number.

The syntax accepted by this parser is the same as for rational.

Note: This function is almost ten times faster than rational, but is slightly less accurate.

The Double type supports about 16 decimal places of accuracy. For 94.2% of numbers, this function and rational give identical results, but for the remaining 5.8%, this function loses precision around the 15th decimal place. For 0.001% of numbers, this function will lose precision at the 13th or 14th decimal place.

rational :: RealFloat a => Parser aSource

Parse a rational number.

This parser accepts an optional leading sign character, followed by at least one decimal digit. The syntax similar to that accepted by the read function, with the exception that a trailing '.' or 'e' not followed by a number is not consumed.

Examples with behaviour identical to read, if you feed an empty continuation to the first result:

rational "3"     == Done 3.0 ""
rational "3.1"   == Done 3.1 ""
rational "3e4"   == Done 30000.0 ""
rational "3.1e4" == Done 31000.0 ""

Examples with behaviour identical to read:

rational ".3"    == Fail "input does not start with a digit"
rational "e3"    == Fail "input does not start with a digit"

Examples of differences from read:

rational "3.foo" == Done 3.0 ".foo"
rational "3e"    == Done 3.0 "e"

State observation and manipulation functions

endOfInput :: Parser ()Source

Match only if all input has been consumed.

atEnd :: Parser BoolSource

Return an indication of whether the end of input has been reached.

Applicative specializations

We provide specializations of <* and *> as <*. and .*>, respectively. Together with IsString instance of Parser, you may write parsers applicatively more easily. For example:

 paren p = "(" .*> p <*. ")"

instead of the more verbose

 paren p = string "(" *> p <* string ")"

(<*.) :: Applicative f => f a -> f Text -> f aSource

Same as Applicative's <* but specialized to Text on the second argument.

(.*>) :: Applicative f => f Text -> f a -> f aSource

Same as Applicative's *> but specialized to Text on the first argument.