attoparsec-0.14.1: Fast combinator parsing for bytestrings and text
CopyrightBryan O'Sullivan 2007-2015
LicenseBSD3
Maintainerbos@serpentine.com
Stabilityexperimental
Portabilityunknown
Safe HaskellTrustworthy
LanguageHaskell2010

Data.Attoparsec.ByteString.Lazy

Description

Simple, efficient combinator parsing that can consume lazy ByteString strings, loosely based on the Parsec library.

This is essentially the same code as in the Attoparsec module, only with a parse function that can consume a lazy ByteString incrementally, and a Result type that does not allow more input to be fed in. Think of this as suitable for use with a lazily read file, e.g. via readFile or hGetContents.

Note: The various parser functions and combinators such as string still expect strict ByteString parameters, and return strict ByteString results. Behind the scenes, strict ByteString values are still used internally to store parser input and manipulate it efficiently.

Synopsis

Documentation

data Result r Source #

The result of a parse.

Constructors

Fail ByteString [String] String

The parse failed. The ByteString is the input that had not yet been consumed when the failure occurred. The [String] is a list of contexts in which the error occurred. The String is the message describing the error, if any.

Done ByteString r

The parse succeeded. The ByteString is the input that had not yet been consumed (if any) when the parse succeeded.

Instances

Instances details
Functor Result Source # 
Instance details

Defined in Data.Attoparsec.ByteString.Lazy

Methods

fmap :: (a -> b) -> Result a -> Result b #

(<$) :: a -> Result b -> Result a #

Show r => Show (Result r) Source # 
Instance details

Defined in Data.Attoparsec.ByteString.Lazy

Methods

showsPrec :: Int -> Result r -> ShowS #

show :: Result r -> String #

showList :: [Result r] -> ShowS #

NFData r => NFData (Result r) Source # 
Instance details

Defined in Data.Attoparsec.ByteString.Lazy

Methods

rnf :: Result r -> () #

compareResults :: (Eq i, Eq r) => IResult i r -> IResult i r -> Maybe Bool Source #

Compare two IResult values for equality.

If both IResults are Partial, the result will be Nothing, as they are incomplete and hence their equality cannot be known. (This is why there is no Eq instance for IResult.)

endOfInput :: forall t. Chunk t => Parser t () Source #

Match only if all input has been consumed.

atEnd :: Chunk t => Parser t Bool Source #

Return an indication of whether the end of input has been reached.

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.

(<?>) infix 0 Source #

Arguments

:: Parser i a 
-> String

the name to use if parsing fails

-> Parser i a 

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.

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

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 ',')

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.

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.

count :: Monad m => Int -> m a -> m [a] Source #

Apply the given action repeatedly, returning every result.

eitherP :: Alternative f => f a -> f b -> f (Either a b) Source #

Combine two alternatives.

feed :: Monoid i => IResult i r -> i -> IResult i r Source #

If a parser has returned a Partial result, supply it with more input.

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 <= 57

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

satisfyWith :: (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.

take :: Int -> Parser ByteString Source #

Consume exactly n bytes of input.

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.

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.

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.

takeWhileIncluding :: (Word8 -> Bool) -> Parser ByteString Source #

Consume input until immediately after the predicate returns True, and return the consumed input.

This parser will consume at least one Word8 or fail.

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.

getChunk :: Parser (Maybe ByteString) Source #

Return the rest of the current chunk without consuming anything.

If the current chunk is empty, then ask for more input. If there is no more input, then return Nothing

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.

takeWhile1 :: (Word8 -> Bool) -> Parser ByteString Source #

Consume input as long as the predicate returns True, and return the consumed input.

This parser requires the predicate to succeed on at least one byte of input: it will fail if the predicate never returns True or if there is no input left.

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.

anyWord8 :: Parser Word8 Source #

Match any byte.

word8 :: Word8 -> Parser Word8 Source #

Match a specific byte.

notWord8 :: Word8 -> Parser Word8 Source #

Match any byte except the given one.

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.

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.

Running parsers

parse :: Parser a -> ByteString -> Result a Source #

Run a parser and return its result.

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)
 

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 #

Convert a Result value to a Maybe value.

eitherResult :: Result r -> Either String r Source #

Convert a Result value to an Either value.