Cabal-1.22.6.0: A framework for packaging Haskell software

Portabilityportable
Maintainerlibraries@haskell.org
Safe HaskellSafe-Inferred

Distribution.Compat.ReadP

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".

See also Koen's paper Parallel Parsing Processes (http://citeseerx.ist.psu.edu/viewdoc/summary?doi=10.1.1.19.9217).

This version of ReadP has been locally hacked to make it H98, by Martin Sjögren mailto:msjogren@gmail.com

The unit tests have been moved to UnitTest.Distribution.Compat.ReadP, by Mark Lentczner mailto:mark@glyphic.com

Synopsis

The ReadP type

type ReadP r a = Parser r Char a

Primitive operations

get :: ReadP r Char

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

look :: ReadP r String

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

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

Symmetric choice.

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

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

gather :: ReadP (String -> P Char r) a -> ReadP r (String, a)

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.

Other operations

pfail :: ReadP r a

Always fails.

satisfy :: (Char -> Bool) -> ReadP r Char

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

char :: Char -> ReadP r Char

Parses and returns the specified character.

string :: String -> ReadP r String

Parses and returns the specified string.

munch :: (Char -> Bool) -> ReadP r String

Parses the first zero or more characters satisfying the predicate.

munch1 :: (Char -> Bool) -> ReadP r String

Parses the first one or more characters satisfying the predicate.

skipSpaces :: ReadP r ()

Skips all whitespace.

choice :: [ReadP r a] -> ReadP r a

Combines all parsers in the specified list.

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

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

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

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

option :: a -> ReadP r a -> ReadP r a

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

optional :: ReadP r a -> ReadP r ()

optional p optionally parses p and always returns ().

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

Parses zero or more occurrences of the given parser.

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

Parses one or more occurrences of the given parser.

skipMany :: ReadP r a -> ReadP r ()

Like many, but discards the result.

skipMany1 :: ReadP r a -> ReadP r ()

Like many1, but discards the result.

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

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

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

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

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

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

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

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

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

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 r a -> ReadP r (a -> a -> a) -> a -> ReadP r a

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 r a -> ReadP r (a -> a -> a) -> ReadP r a

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

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

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

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

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 = String -> [(a, String)]

readP_to_S :: ReadP a a -> ReadS a

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 -> String -> [(a,String)]

readS_to_P :: ReadS a -> ReadP r a

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