bytestringreadp-0.2: A ReadP style parser library for ByteString

Portabilitynon-portable (local universal quantification)
Stabilityprovisional
Maintainergracjanpolak@gmail.com

Text.ParserCombinators.ReadP.ByteString

Contents

Description

This is a library of parser combinators, originally written by Koen Claessen. It parses all alternatives in parallel, so it never keeps hold of the beginning of the input string, a common source of space leaks with other parsers. The '(+++)' choice combinator is genuinely commutative; it makes no difference which branch is "shorter".

Adapted to use Data.ByteString by Gracjan Polak. Designed as a drop-in replacement for Text.ParserCombinators.ReadP.

Synopsis

The ReadP type

Primitive operations

look :: ReadP ByteStringSource

Look-ahead: returns the part of the input that is left, without consuming it.

(+++) :: ReadP a -> ReadP a -> ReadP aSource

Symmetric choice.

(<++) :: ReadP a -> ReadP a -> ReadP aSource

Local, exclusive, left-biased choice: If left parser locally produces any result at all, then right parser is not used.

countsym :: ReadP a -> ReadP (Int, a)Source

Transforms a parser into one that does the same, but in addition returns the exact number of characters read. IMPORTANT NOTE: countsym gives a runtime error if its first argument is built using any occurrences of readS_to_P.

Other operations

get :: ReadP Word8Source

Consumes and returns the next character. Fails if there is no input left.

pfail :: ReadP aSource

Always fails.

satisfy :: (Word8 -> Bool) -> ReadP Word8Source

Consumes and returns the next character, if it satisfies the specified predicate.

char :: Word8 -> ReadP Word8Source

Parses and returns the specified character.

string :: ByteString -> ReadP ByteStringSource

Parses and returns the specified string.

gather :: ReadP a -> ReadP (ByteString, a)Source

Transforms a parser into one that does the same, but in addition returns the exact characters read. IMPORTANT NOTE: gather gives a runtime error if its first argument is built using any occurrences of readS_to_P.

munch :: (Word8 -> Bool) -> ReadP ByteStringSource

Parses the first zero or more characters satisfying the predicate.

munch1 :: (Word8 -> Bool) -> ReadP ByteStringSource

Parses the first one or more characters satisfying the predicate.

skipSpaces :: ReadP ()Source

Skips all whitespace.

choice :: [ReadP a] -> ReadP aSource

Combines all parsers in the specified list.

count :: Int -> ReadP a -> ReadP [a]Source

count n p parses n occurrences of p in sequence. A list of results is returned.

between :: ReadP open -> ReadP close -> ReadP a -> ReadP aSource

between open close p parses open, followed by p and finally close. Only the value of p is returned.

option :: a -> ReadP a -> ReadP aSource

option x p will either parse p or return x without consuming any input.

optional :: ReadP a -> ReadP ()Source

optional p optionally parses p and always returns ().

many :: ReadP a -> ReadP [a]Source

Parses zero or more occurrences of the given parser.

many1 :: ReadP a -> ReadP [a]Source

Parses one or more occurrences of the given parser.

skipMany :: ReadP a -> ReadP ()Source

Like many, but discards the result.

skipMany1 :: ReadP a -> ReadP ()Source

Like many1, but discards the result.

sepBy :: ReadP a -> ReadP sep -> ReadP [a]Source

sepBy p sep parses zero or more occurrences of p, separated by sep. Returns a list of values returned by p.

sepBy1 :: ReadP a -> ReadP sep -> ReadP [a]Source

sepBy1 p sep parses one or more occurrences of p, separated by sep. Returns a list of values returned by p.

endBy :: ReadP a -> ReadP sep -> ReadP [a]Source

endBy p sep parses zero or more occurrences of p, separated and ended by sep.

endBy1 :: ReadP a -> ReadP sep -> ReadP [a]Source

endBy p sep parses one or more occurrences of p, separated and ended by sep.

chainr :: ReadP a -> ReadP (a -> a -> a) -> a -> ReadP aSource

chainr p op x parses zero or more occurrences of p, separated by op. Returns a value produced by a right associative application of all functions returned by op. If there are no occurrences of p, x is returned.

chainl :: ReadP a -> ReadP (a -> a -> a) -> a -> ReadP aSource

chainl p op x parses zero or more occurrences of p, separated by op. Returns a value produced by a left associative application of all functions returned by op. If there are no occurrences of p, x is returned.

chainl1 :: ReadP a -> ReadP (a -> a -> a) -> ReadP aSource

Like chainl, but parses one or more occurrences of p.

chainr1 :: ReadP a -> ReadP (a -> a -> a) -> ReadP aSource

Like chainr, but parses one or more occurrences of p.

manyTill :: ReadP a -> ReadP end -> ReadP [a]Source

manyTill p end parses zero or more occurrences of p, until end succeeds. Returns a list of values returned by p.

Running a parser

type ReadS a = ByteString -> [(a, ByteString)]Source

A parser for a type a, represented as a function that takes a ByteString and returns a list of possible parses as (a,ByteString) pairs.

Note that this kind of backtracking parser is very inefficient; reading a large structure may be quite slow (cf ReadP).

readP_to_S :: ReadP a -> ReadS aSource

Converts a parser into a Haskell ReadS-style function. This is the main way in which you can "run" a ReadP parser: the expanded type is readP_to_S :: ReadP a -> ByteString -> [(a,ByteString)]

readS_to_P :: ReadS a -> ReadP aSource

Converts a Haskell ReadS-style function into a parser. Warning: This introduces local backtracking in the resulting parser, and therefore a possible inefficiency.