attoparsec-0.13.2.2: Fast combinator parsing for bytestrings and text

CopyrightBryan O'Sullivan 2007-2015
LicenseBSD3
Maintainerbos@serpentine.com
Stabilityexperimental
Portabilityunknown
Safe HaskellTrustworthy
LanguageHaskell98

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 makes several tradeoffs. It is not intended for, or ideal for, all possible uses.

  • While attoparsec 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 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 does not support being used as a monad transformer.
  • attoparsec is specialised to deal only with strict Text input. Efficiency concerns rule out both lists and lazy text. The usual use for lazy text would be to allow consumption of very large input without a large footprint. For this need, attoparsec's incremental input provides an excellent substitute, with much more control over when input takes place. If you must use lazy text, see the Lazy module, which feeds lazy chunks to a regular parser.
  • Parsec parsers can produce more helpful error messages than attoparsec parsers. This is a matter of focus: attoparsec avoids the extra book-keeping in favour of higher performance.

Incremental input

attoparsec 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 string will resume parsing at the point where it was suspended, with the string you supplied used as new input at the end of the existing input. 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.

Note: incremental input does not imply that attoparsec will release portions of its internal state for garbage collection as it proceeds. Its internal representation is equivalent to a single Text: if you feed incremental input to an a parser, it will require memory proportional to the amount of input you supply. (This is necessary to support arbitrary backtracking.)

Performance considerations

If you write an attoparsec-based parser carefully, it can be realistic to expect it to perform similarly to a hand-rolled C parser (measuring megabytes parsed per second).

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 = c == '\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 IResult i r Source #

The result of a parse. This is parameterised over the type i of string that was processed.

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

Constructors

Fail i [String] String

The parse failed. The i parameter 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 (i -> IResult i r)

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

Note: if you get a Partial result, do not call its continuation more than once.

Done i r

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

Instances

Functor (IResult i) Source # 

Methods

fmap :: (a -> b) -> IResult i a -> IResult i b #

(<$) :: a -> IResult i b -> IResult i a #

(Show i, Show r) => Show (IResult i r) Source # 

Methods

showsPrec :: Int -> IResult i r -> ShowS #

show :: IResult i r -> String #

showList :: [IResult i r] -> ShowS #

(NFData i, NFData r) => NFData (IResult i r) Source # 

Methods

rnf :: IResult i r -> () #

compareResults :: (Eq i, Eq r) => IResult i r -> IResult i r -> Maybe Bool Source #

Compare two IResult values for equality.

If both IResults are Partial, the result will be Nothing, as they are incomplete and hence their equality cannot be known. (This is why there is no Eq instance for IResult.)

Running parsers

parse :: Parser a -> Text -> Result a Source #

Run a parser.

feed :: Monoid i => IResult i r -> i -> IResult i r Source #

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

parseOnly :: Parser a -> Text -> Either String a Source #

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

This function does not force a parser to consume all of its input. Instead, any residual input will be discarded. To force a parser to consume all of its input, use something like this:

parseOnly (myParser <* endOfInput)
 

parseWith Source #

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 r Source #

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

eitherResult :: Result r -> Either String r Source #

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

Parsing individual characters

char :: Char -> Parser Char Source #

Match a specific character.

anyChar :: Parser Char Source #

Match any character.

notChar :: Char -> Parser Char Source #

Match any character except the given one.

satisfy :: (Char -> Bool) -> Parser Char Source #

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

digit = satisfy isDigit
    where isDigit c = c >= '0' && c <= '9'

satisfyWith :: (Char -> a) -> (a -> Bool) -> Parser a Source #

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.

skipDigit = skip isDigit
    where isDigit c = c >= '0' && c <= '9'

Lookahead

peekChar :: Parser (Maybe Char) Source #

Match any character, to perform lookahead. Returns Nothing if end of input has been reached. Does not consume any 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.

peekChar' :: Parser Char Source #

Match any character, to perform lookahead. Does not consume any input, but will fail if end of input has been reached.

Special character parsers

digit :: Parser Char Source #

Parse a single digit, as recognised by isDigit.

letter :: Parser Char Source #

Parse a letter, as recognised by isAlpha.

space :: Parser Char Source #

Parse a space character, as recognised by isSpace.

Character classes

inClass :: String -> Char -> Bool Source #

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 -> Bool Source #

Match any character not in a set.

Efficient string handling

string :: Text -> Parser Text Source #

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 the first branch is a partial match, and will consume the letters 'f' and 'o' before failing. In attoparsec, the above parser will succeed on that input, because the failed first branch will consume nothing.

stringCI :: Text -> Parser Text Source #

Deprecated: this is very inefficient, use asciiCI instead

Satisfy a literal string, ignoring case.

Note: this function is currently quite inefficient. Unicode case folding can change the length of a string ("ß" becomes "ss"), which makes a simple, efficient implementation tricky. We have (for now) chosen simplicity over efficiency.

asciiCI :: Text -> Parser Text Source #

Satisfy a literal string, ignoring case for characters in the ASCII range.

skipSpace :: Parser () Source #

Skip over white space.

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

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

scan :: s -> (s -> Char -> Maybe s) -> Parser Text Source #

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.

runScanner :: s -> (s -> Char -> Maybe s) -> Parser (Text, s) Source #

Like scan, but generalized to return the final state of the scanner.

take :: Int -> Parser Text Source #

Consume exactly n characters of input.

takeWhile :: (Char -> Bool) -> Parser Text Source #

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 Text Source #

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 Text Source #

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.

String combinators

If you enable the OverloadedStrings language extension, you can use the *> and <* combinators to simplify the common task of matching a statically known string, then immediately parsing something else.

Instead of writing something like this:

string "foo" *> wibble
 

Using OverloadedStrings, you can omit the explicit use of string, and write a more compact version:

"foo" *> wibble

(Note: the .*> and <*. combinators that were originally provided for this purpose are obsolete and unnecessary, and will be removed in the next major version.)

(.*>) :: Text -> Parser a -> Parser a Source #

Deprecated: This is no longer necessary, and will be removed. Use *> instead.

Obsolete. A type-specialized version of *> for Text. Use *> instead.

(<*.) :: Parser a -> Text -> Parser a Source #

Deprecated: This is no longer necessary, and will be removed. Use <* instead.

Obsolete. A type-specialized version of <* for Text. Use *> instead.

Consume all remaining input

takeText :: Parser Text Source #

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

takeLazyText :: Parser Text Source #

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".

isEndOfLine :: Char -> Bool Source #

A predicate that matches either a carriage return '\r' or newline '\n' character.

isHorizontalSpace :: Char -> Bool Source #

A predicate that matches either a space ' ' or horizontal tab '\t' character.

Numeric parsers

decimal :: Integral a => Parser a Source #

Parse and decode an unsigned decimal number.

hexadecimal :: (Integral a, Bits a) => Parser a Source #

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 a Source #

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

double :: Parser Double Source #

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"

This function does not accept string representations of "NaN" or "Infinity".

data Number Source #

A numeric type that can represent integers accurately, and floating point numbers to the precision of a Double.

Note: this type is deprecated, and will be removed in the next major release. Use the Scientific type instead.

Constructors

I !Integer 
D !Double 

Instances

Eq Number Source # 

Methods

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

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

Fractional Number Source # 
Data Number Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Number -> c Number #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Number #

toConstr :: Number -> Constr #

dataTypeOf :: Number -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Number) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Number) #

gmapT :: (forall b. Data b => b -> b) -> Number -> Number #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Number -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Number -> r #

gmapQ :: (forall d. Data d => d -> u) -> Number -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Number -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Number -> m Number #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Number -> m Number #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Number -> m Number #

Num Number Source # 
Ord Number Source # 
Real Number Source # 
RealFrac Number Source # 

Methods

properFraction :: Integral b => Number -> (b, Number) #

truncate :: Integral b => Number -> b #

round :: Integral b => Number -> b #

ceiling :: Integral b => Number -> b #

floor :: Integral b => Number -> b #

Show Number Source # 
NFData Number Source # 

Methods

rnf :: Number -> () #

number :: Parser Number Source #

Deprecated: Use scientific instead.

Parse a number, attempting to preserve both speed and precision.

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

This function does not accept string representations of "NaN" or "Infinity".

rational :: Fractional a => Parser a Source #

Parse a rational number.

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

Note: this parser is not safe for use with inputs from untrusted sources. An input with a suitably large exponent such as "1e1000000000" will cause a huge Integer to be allocated, resulting in what is effectively a denial-of-service attack.

In most cases, it is better to use double or scientific instead.

scientific :: Parser Scientific Source #

Parse a scientific number.

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

Combinators

try :: Parser i a -> Parser i a Source #

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

This combinator is provided for compatibility with Parsec. attoparsec parsers always backtrack on failure.

(<?>) infix 0 Source #

Arguments

:: Parser i a 
-> String

the name to use if parsing fails

-> Parser i a 

Name the parser, in case failure occurs.

choice :: Alternative f => [f a] -> f a Source #

choice ps tries to apply the actions in the list ps in order, until one of them succeeds. Returns the value of the succeeding action.

count :: Monad m => Int -> m a -> m [a] Source #

Apply the given action repeatedly, returning every result.

option :: Alternative f => a -> f a -> f a Source #

option x p tries to apply action p. If p fails without consuming input, it returns the value x, otherwise the value returned by p.

priority  = option 0 (digitToInt <$> digit)

many' :: MonadPlus m => m a -> m [a] Source #

many' p applies the action p zero or more times. Returns a list of the returned values of p. The value returned by p is forced to WHNF.

 word  = many' letter

many1 :: Alternative f => f a -> f [a] Source #

many1 p applies the action p one or more times. Returns a list of the returned values of p.

 word  = many1 letter

many1' :: MonadPlus m => m a -> m [a] Source #

many1' p applies the action p one or more times. Returns a list of the returned values of p. The value returned by p is forced to WHNF.

 word  = many1' letter

manyTill :: Alternative f => f a -> f b -> f [a] Source #

manyTill p end applies action p zero or more times until action end succeeds, and returns the list of values returned by p. This can be used to scan comments:

 simpleComment   = string "<!--" *> manyTill anyChar (string "-->")

(Note the overlapping parsers anyChar and string "-->". While this will work, it is not very efficient, as it will cause a lot of backtracking.)

manyTill' :: MonadPlus m => m a -> m b -> m [a] Source #

manyTill' p end applies action p zero or more times until action end succeeds, and returns the list of values returned by p. This can be used to scan comments:

 simpleComment   = string "<!--" *> manyTill' anyChar (string "-->")

(Note the overlapping parsers anyChar and string "-->". While this will work, it is not very efficient, as it will cause a lot of backtracking.)

The value returned by p is forced to WHNF.

sepBy :: Alternative f => f a -> f s -> f [a] Source #

sepBy p sep applies zero or more occurrences of p, separated by sep. Returns a list of the values returned by p.

commaSep p  = p `sepBy` (char ',')

sepBy' :: MonadPlus m => m a -> m s -> m [a] Source #

sepBy' p sep applies zero or more occurrences of p, separated by sep. Returns a list of the values returned by p. The value returned by p is forced to WHNF.

commaSep p  = p `sepBy'` (char ',')

sepBy1 :: Alternative f => f a -> f s -> f [a] Source #

sepBy1 p sep applies one or more occurrences of p, separated by sep. Returns a list of the values returned by p.

commaSep p  = p `sepBy1` (char ',')

sepBy1' :: MonadPlus m => m a -> m s -> m [a] Source #

sepBy1' p sep applies one or more occurrences of p, separated by sep. Returns a list of the values returned by p. The value returned by p is forced to WHNF.

commaSep p  = p `sepBy1'` (char ',')

skipMany :: Alternative f => f a -> f () Source #

Skip zero or more instances of an action.

skipMany1 :: Alternative f => f a -> f () Source #

Skip one or more instances of an action.

eitherP :: Alternative f => f a -> f b -> f (Either a b) Source #

Combine two alternatives.

match :: Parser a -> Parser (Text, a) Source #

Return both the result of a parse and the portion of the input that was consumed while it was being parsed.

State observation and manipulation functions

endOfInput :: forall t. Chunk t => Parser t () Source #

Match only if all input has been consumed.

atEnd :: Chunk t => Parser t Bool Source #

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