Portability | unknown |
---|---|
Stability | experimental |
Maintainer | bos@serpentine.com |
Safe Haskell | Safe-Infered |
Simple, efficient combinator parsing for ByteString
strings,
loosely based on the Parsec library.
- type Parser = Parser ByteString
- type Result = IResult ByteString
- data IResult t r
- parse :: Parser a -> ByteString -> Result a
- feed :: Result r -> ByteString -> Result r
- parseOnly :: Parser a -> ByteString -> Either String a
- parseWith :: Monad m => m ByteString -> Parser a -> ByteString -> m (Result a)
- parseTest :: Show a => Parser a -> ByteString -> IO ()
- maybeResult :: Result r -> Maybe r
- eitherResult :: Result r -> Either String r
- (<?>) :: Parser a -> String -> Parser a
- try :: Parser a -> Parser a
- module Data.Attoparsec.Combinator
- word8 :: Word8 -> Parser Word8
- anyWord8 :: Parser Word8
- notWord8 :: Word8 -> Parser Word8
- satisfy :: (Word8 -> Bool) -> Parser Word8
- satisfyWith :: (Word8 -> a) -> (a -> Bool) -> Parser a
- skip :: (Word8 -> Bool) -> Parser ()
- inClass :: String -> Word8 -> Bool
- notInClass :: String -> Word8 -> Bool
- string :: ByteString -> Parser ByteString
- skipWhile :: (Word8 -> Bool) -> Parser ()
- take :: Int -> Parser ByteString
- scan :: s -> (s -> Word8 -> Maybe s) -> Parser ByteString
- takeWhile :: (Word8 -> Bool) -> Parser ByteString
- takeWhile1 :: (Word8 -> Bool) -> Parser ByteString
- takeTill :: (Word8 -> Bool) -> Parser ByteString
- takeByteString :: Parser ByteString
- takeLazyByteString :: Parser ByteString
- endOfInput :: Parser ()
- atEnd :: Parser Bool
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
andstring
. If you use complicated combinators that return lists of bytes or 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
ByteString
input. Efficiency concerns rule out both lists and lazy bytestrings. The usual use for lazy bytestrings 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 bytestrings, see theLazy
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 bytestring 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 bytestring 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 bytestring.
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
If you write an Attoparsec-based parser carefully, it can be realistic to expect it to perform within a factor of 2 of 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 ByteString
-oriented parsers whenever possible,
e.g. takeWhile1
instead of many1
anyWord8
. There is
about a factor of 100 difference in performance between the two
kinds of parser.
For very simple byte-testing predicates, write them by hand instead
of using inClass
or notInClass
. For instance, both of
these predicates test for an end-of-line byte, but the first is
much faster than the second:
endOfLine_fast w = w == 13 || w == 10 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
type Parser = Parser ByteStringSource
type Result = IResult ByteStringSource
The result of a parse. This is parameterised over the type t
of string that was processed.
This type is an instance of Functor
, where fmap
transforms the
value in a Done
result.
Fail t [String] String | The parse failed. The |
Partial (t -> IResult t 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 t r | The parse succeeded. The |
Running parsers
parse :: Parser a -> ByteString -> Result aSource
Run a parser.
feed :: Result r -> ByteString -> Result rSource
If a parser has returned a Partial
result, supply it with more
input.
parseOnly :: Parser a -> ByteString -> Either String aSource
Run a parser that cannot be resupplied via a Partial
result.
:: Monad m | |
=> m ByteString | An action that will be executed to provide the parser
with more input, if necessary. The action must return an
|
-> Parser a | |
-> ByteString | 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 -> ByteString -> IO ()Source
Run a parser and print its result to standard output.
Result conversion
maybeResult :: Result r -> Maybe rSource
eitherResult :: Result r -> Either String rSource
Combinators
Name the parser, in case failure occurs.
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 provided for compatibility with Parsec. Attoparsec parsers always backtrack on failure.
module Data.Attoparsec.Combinator
Parsing individual bytes
satisfy :: (Word8 -> Bool) -> Parser Word8Source
The parser satisfy p
succeeds for any byte for which the
predicate p
returns True
. Returns the byte that is actually
parsed.
digit = satisfy isDigit where isDigit w = w >= 48 && w <= 57
satisfyWith :: (Word8 -> a) -> (a -> Bool) -> Parser aSource
The parser satisfyWith f p
transforms a byte, and succeeds if
the predicate p
returns True
on the transformed value. The
parser returns the transformed byte that was parsed.
skip :: (Word8 -> Bool) -> Parser ()Source
The parser skip p
succeeds for any byte for which the predicate
p
returns True
.
skipDigit = skip isDigit where isDigit w = w >= 48 && w <= 57
Byte classes
inClass :: String -> Word8 -> BoolSource
Match any byte 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 -> Word8 -> BoolSource
Match any byte not in a set.
Efficient string handling
string :: ByteString -> Parser ByteStringSource
string s
parses a sequence of bytes 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, the above parser will succeed on
that input, because the failed first branch will consume nothing.
skipWhile :: (Word8 -> Bool) -> Parser ()Source
Skip past input for as long as the predicate returns True
.
take :: Int -> Parser ByteStringSource
Consume exactly n
bytes of input.
scan :: s -> (s -> Word8 -> Maybe s) -> Parser ByteStringSource
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 byte 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 byte 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 :: (Word8 -> Bool) -> Parser ByteStringSource
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 byte 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 :: (Word8 -> Bool) -> Parser ByteStringSource
takeTill :: (Word8 -> Bool) -> Parser ByteStringSource
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 byte 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
takeByteString :: Parser ByteStringSource
Consume all remaining input and return it as a single string.
takeLazyByteString :: Parser ByteStringSource
Consume all remaining input and return it as a single string.
State observation and manipulation functions
Match only if all input has been consumed.