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

Portabilityunknown
Stabilityexperimental
Maintainerbos@serpentine.com

Data.Attoparsec.Incremental.Char8

Contents

Description

Simple, efficient, character-oriented, and incremental parser combinators for lazy L.ByteString strings, loosely based on the Parsec library.

Note: This module is intended for parsing text that is represented using an 8-bit character set, e.g. ASCII or ISO-8859-15. It does not deal with character encodings, multibyte characters, or wide characters. Any attempts to use characters above code point 255 will give wrong answers.

Synopsis

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 characters

satisfy :: (Char -> Bool) -> Parser r CharSource

Character parser.

char :: Char -> Parser r CharSource

Match a specific character.

notChar :: Char -> Parser r CharSource

Match any character except the given one.

Character classes

inClass :: String -> Char -> BoolSource

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

Match any character not in a set.

Efficient string handling

string :: ByteString -> Parser r ByteStringSource

Match a literal string exactly.

skipSpace :: Parser r ()Source

Skip over white space.

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

Skip over characters while the predicate succeeds.

takeCount :: Int -> Parser r ByteStringSource

Return exactly the given number of bytes. If not enough are available, fail.

takeTill :: (Char -> Bool) -> Parser r ByteStringSource

Consume characters while the predicate fails.

takeWhile :: (Char -> Bool) -> Parser r ByteStringSource

Consume characters while the predicate succeeds.

Text parsing

endOfLine :: Parser r ()Source

Match the end of a line. This may be any of a newline character, a carriage return character, or a carriage return followed by a newline.

Numeric parsers

int :: Parser r IntSource

Parse an Int.

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