attoparsec-0.7.2: Fast combinator parsing with Data.ByteString.Lazy

Portabilityunknown
Stabilityexperimental
Maintainerbos@serpentine.com

Data.Attoparsec.Incremental

Contents

Description

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.

Synopsis

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

data Parser r a Source

The parser type.

data Result a Source

The result of a partial parse.

Constructors

Failed String

The parse failed, with the given error message.

Done ByteString a

The parse succeeded, producing the given result. The ByteString contains any unconsumed input.

Partial (ByteString -> Result a)

The parse ran out of data before finishing. To resume the parse, pass more data to the given continuation.

Instances

Show a => Show (Result a) 

Running parsers

parse :: Parser r r -> ByteString -> Result rSource

Run a parser.

parseWithSource

Arguments

:: 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

(<?>)Source

Arguments

:: Parser r a 
-> String

the name to use if parsing fails

-> Parser r a 

Name the parser, in case failure occurs.

try :: Parser r a -> Parser r aSource

This is a no-op combinator for compatibility.

Parsing individual bytes

word8 :: Word8 -> Parser r Word8Source

Match a specific byte.

notWord8 :: Word8 -> Parser r Word8Source

Match any byte except the given one.

anyWord8 :: Parser r Word8Source

Match any byte.

satisfy :: (Word8 -> Bool) -> Parser r Word8Source

Match a single byte based on the given predicate.

Efficient string handling

string :: ByteString -> Parser r ByteStringSource

Match a literal string exactly.

skipWhile :: (Word8 -> Bool) -> Parser r ()Source

Skip over bytes while the predicate is true.

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.

yield :: Parser r ()Source

Resume our caller, handing back a Partial result. This function is probably not useful, but provided for completeness.

Combinators