| Copyright | Bryan O'Sullivan 2007-2015 | 
|---|---|
| License | BSD3 | 
| Maintainer | bos@serpentine.com | 
| Stability | experimental | 
| Portability | unknown | 
| Safe Haskell | Trustworthy | 
| Language | Haskell98 | 
Data.Attoparsec.ByteString
Contents
Description
Simple, efficient combinator parsing for ByteString strings,
 loosely based on the Parsec library.
- type Parser = Parser ByteString
- type Result = IResult ByteString
- data IResult i r
- compareResults :: (Eq i, Eq r) => IResult i r -> IResult i r -> Maybe Bool
- parse :: Parser a -> ByteString -> Result a
- feed :: Monoid i => IResult i r -> i -> IResult i 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
- 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 ()
- peekWord8 :: Parser (Maybe Word8)
- peekWord8' :: Parser Word8
- 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
- runScanner :: s -> (s -> Word8 -> Maybe s) -> Parser (ByteString, s)
- takeWhile :: (Word8 -> Bool) -> Parser ByteString
- takeWhile1 :: (Word8 -> Bool) -> Parser ByteString
- takeTill :: (Word8 -> Bool) -> Parser ByteString
- takeByteString :: Parser ByteString
- takeLazyByteString :: Parser ByteString
- try :: Parser i a -> Parser i a
- (<?>) :: Parser i a -> String -> Parser i a
- choice :: Alternative f => [f a] -> f a
- count :: Monad m => Int -> m a -> m [a]
- option :: Alternative f => a -> f a -> f a
- many' :: MonadPlus m => m a -> m [a]
- many1 :: Alternative f => f a -> f [a]
- many1' :: MonadPlus m => m a -> m [a]
- manyTill :: Alternative f => f a -> f b -> f [a]
- manyTill' :: MonadPlus m => m a -> m b -> m [a]
- sepBy :: Alternative f => f a -> f s -> f [a]
- sepBy' :: MonadPlus m => m a -> m s -> m [a]
- sepBy1 :: Alternative f => f a -> f s -> f [a]
- sepBy1' :: MonadPlus m => m a -> m s -> m [a]
- skipMany :: Alternative f => f a -> f ()
- skipMany1 :: Alternative f => f a -> f ()
- eitherP :: Alternative f => f a -> f b -> f (Either a b)
- match :: Parser a -> Parser (ByteString, a)
- endOfInput :: forall t. Chunk t => Parser t ()
- atEnd :: Chunk t => Parser t 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 takeWhileandstring. 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 ByteStringinput. 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 the Data.Attoparsec.ByteString.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 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 a bytestring will
 resume parsing at the point where it was suspended, with the
 bytestring 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 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.
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
 ByteString: if you feed incremental input to 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 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 ByteString Source
type Result = IResult ByteString 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  | 
| 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  | 
| Done i r | The parse succeeded.  The  | 
Running parsers
parse :: Parser a -> ByteString -> 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 -> ByteString -> 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)
Arguments
| :: 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 r Source
eitherResult :: Result r -> Either String r Source
Parsing individual bytes
satisfy :: (Word8 -> Bool) -> Parser Word8 Source
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 <= 57satisfyWith :: (Word8 -> a) -> (a -> Bool) -> Parser a Source
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 <= 57Lookahead
peekWord8 :: Parser (Maybe Word8) Source
Match any byte, 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.
peekWord8' :: Parser Word8 Source
Match any byte, to perform lookahead. Does not consume any input, but will fail if end of input has been reached.
Byte classes
inClass :: String -> Word8 -> Bool Source
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 -> Bool Source
Match any byte not in a set.
Efficient string handling
string :: ByteString -> Parser ByteString Source
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 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 ByteString Source
Consume exactly n bytes of input.
scan :: s -> (s -> Word8 -> Maybe s) -> Parser ByteString 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 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.
runScanner :: s -> (s -> Word8 -> Maybe s) -> Parser (ByteString, s) Source
Like scan, but generalized to return the final state of the
 scanner.
takeWhile :: (Word8 -> Bool) -> Parser ByteString 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 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 ByteString Source
takeTill :: (Word8 -> Bool) -> Parser ByteString 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 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 ByteString Source
Consume all remaining input and return it as a single string.
takeLazyByteString :: Parser ByteString Source
Consume all remaining input and return it as a single string.
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.
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 (ByteString, 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.