Portability | unknown |
---|---|
Stability | experimental |
Maintainer | bos@serpentine.com |
Simple, efficient, and incremental parser combinators for lazy
ByteString
strings, loosely based on the Parsec library.
This module is heavily influenced by Adam Langley's incremental
parser in his binary-strict
package.
- data Parser r a
- data Result a
- = Failed String
- | Done ByteString a
- | Partial (ByteString -> Result a)
- parse :: Parser r r -> ByteString -> Result r
- parseWith :: Applicative f => f ByteString -> Parser r r -> ByteString -> f (Result r)
- parseTest :: Show r => Parser r r -> ByteString -> IO ()
- (<?>) :: Parser r a -> String -> Parser r a
- try :: Parser r a -> Parser r a
- word8 :: Word8 -> Parser r Word8
- notWord8 :: Word8 -> Parser r Word8
- anyWord8 :: Parser r Word8
- satisfy :: (Word8 -> Bool) -> Parser r Word8
- string :: ByteString -> Parser r ByteString
- skipWhile :: (Word8 -> Bool) -> Parser r ()
- takeCount :: Int -> Parser r ByteString
- takeTill :: (Word8 -> Bool) -> Parser r ByteString
- takeWhile :: (Word8 -> Bool) -> Parser r ByteString
- endOfInput :: Parser r ()
- pushBack :: ByteString -> Parser r ()
- yield :: Parser r ()
- module Data.Attoparsec.Combinator
Incremental parsing
Incremental parsing makes it possible to supply a parser with only
a limited amount of input. If the parser cannot complete due to
lack of data, it will return a Partial
result with a continuation
to which more input can be supplied, as follows:
case parse myParser someInput of Partial k -> k moreInput
To signal that no more input is available, pass an empty string to this continuation.
Parser types
The parser type.
Monad (Parser r) | |
Functor (Parser r) | |
MonadPlus (Parser r) | |
Applicative (Parser r) | |
Alternative (Parser r) |
The result of a partial parse.
Failed String | The parse failed, with the given error message. |
Done ByteString a | The parse succeeded, producing the given
result. The |
Partial (ByteString -> Result a) | The parse ran out of data before finishing. To resume the parse, pass more data to the given continuation. |
Running parsers
parse :: Parser r r -> ByteString -> Result rSource
Run a parser.
:: Applicative f | |
=> f ByteString | resupply parser with input |
-> Parser r r | parser to run |
-> ByteString | initial input |
-> f (Result r) |
Run a parser, using the given function to resupply it with input.
Here's an example that shows how to parse data from a socket, using
Johan Tibbell's network-bytestring
package.
import qualified Data.ByteString.Lazy as L import Data.Attoparsec.Incremental (Parser, Result, parseWith) import Network.Socket.ByteString.Lazy (recv_) import Network.Socket (Socket) netParse :: Parser r r -> Socket -> IO (Result r) netParse p sock = parseWith (recv_ sock 65536) p L.empty
parseTest :: Show r => Parser r r -> ByteString -> IO ()Source
Try out a parser, and print its result.
Combinators
Name the parser, in case failure occurs.
Parsing individual bytes
Efficient string handling
string :: ByteString -> Parser r ByteStringSource
Match a literal string exactly.
takeCount :: Int -> Parser r ByteStringSource
Return exactly the given number of bytes. If not enough are available, fail.
takeTill :: (Word8 -> Bool) -> Parser r ByteStringSource
Consume bytes while the predicate fails. If the predicate never succeeds, the entire input string is returned.
takeWhile :: (Word8 -> Bool) -> Parser r ByteStringSource
Consume bytes while the predicate succeeds.
State observation and manipulation functions
endOfInput :: Parser r ()Source
Succeed if we have reached the end of the input string.
pushBack :: ByteString -> Parser r ()Source
Force the given string to appear next in the input stream.
Resume our caller, handing back a Partial
result. This function
is probably not useful, but provided for completeness.
Combinators
module Data.Attoparsec.Combinator