| Copyright | (c) The University of Glasgow 2002 | 
|---|---|
| License | BSD-style (see the file libraries/base/LICENSE) | 
| Maintainer | libraries@haskell.org | 
| Portability | portable | 
| Safe Haskell | None | 
| Language | Haskell2010 | 
Distribution.Compat.ReadP
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
- type ReadP r a = Parser r Char a
- get :: ReadP r Char
- look :: ReadP r String
- (+++) :: ReadP r a -> ReadP r a -> ReadP r a
- (<++) :: ReadP a a -> ReadP r a -> ReadP r a
- gather :: ReadP (String -> P Char r) a -> ReadP r (String, a)
- pfail :: ReadP r a
- eof :: ReadP r ()
- satisfy :: (Char -> Bool) -> ReadP r Char
- char :: Char -> ReadP r Char
- string :: String -> ReadP r String
- munch :: (Char -> Bool) -> ReadP r String
- munch1 :: (Char -> Bool) -> ReadP r String
- skipSpaces :: ReadP r ()
- skipSpaces1 :: ReadP r ()
- choice :: [ReadP r a] -> ReadP r a
- count :: Int -> ReadP r a -> ReadP r [a]
- between :: ReadP r open -> ReadP r close -> ReadP r a -> ReadP r a
- option :: a -> ReadP r a -> ReadP r a
- optional :: ReadP r a -> ReadP r ()
- many :: ReadP r a -> ReadP r [a]
- many1 :: ReadP r a -> ReadP r [a]
- skipMany :: ReadP r a -> ReadP r ()
- skipMany1 :: ReadP r a -> ReadP r ()
- sepBy :: ReadP r a -> ReadP r sep -> ReadP r [a]
- sepBy1 :: ReadP r a -> ReadP r sep -> ReadP r [a]
- endBy :: ReadP r a -> ReadP r sep -> ReadP r [a]
- endBy1 :: ReadP r a -> ReadP r sep -> ReadP r [a]
- chainr :: ReadP r a -> ReadP r (a -> a -> a) -> a -> ReadP r a
- chainl :: ReadP r a -> ReadP r (a -> a -> a) -> a -> ReadP r a
- chainl1 :: ReadP r a -> ReadP r (a -> a -> a) -> ReadP r a
- chainr1 :: ReadP r a -> ReadP r (a -> a -> a) -> ReadP r a
- manyTill :: ReadP r a -> ReadP [a] end -> ReadP r [a]
- type ReadS a = String -> [(a, String)]
- readP_to_S :: ReadP a a -> ReadS a
- readS_to_P :: ReadS a -> ReadP r a
- data Parser r s a
The ReadP type
Primitive operations
Consumes and returns the next character. Fails if there is no input left.
look :: ReadP r String Source #
Look-ahead: returns the part of the input that is left, without consuming it.
(<++) :: ReadP a a -> ReadP r a -> ReadP r a infixr 5 Source #
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) 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.
Other operations
satisfy :: (Char -> Bool) -> ReadP r Char Source #
Consumes and returns the next character, if it satisfies the specified predicate.
munch :: (Char -> Bool) -> ReadP r String Source #
Parses the first zero or more characters satisfying the predicate.
munch1 :: (Char -> Bool) -> ReadP r String Source #
Parses the first one or more characters satisfying the predicate.
skipSpaces :: ReadP r () Source #
Skips all whitespace.
skipSpaces1 :: ReadP r () Source #
Like skipSpaces but succeeds only if there is at least one
 whitespace character to skip.
count :: Int -> ReadP r a -> ReadP r [a] Source #
 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 Source #
 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 Source #
option x p will either parse p or return x without consuming
   any input.
sepBy :: ReadP r a -> ReadP r sep -> ReadP r [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 r a -> ReadP r sep -> ReadP r [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 r a -> ReadP r sep -> ReadP r [a] Source #
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] Source #
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 Source #
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 Source #
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 Source #
Like chainl, but parses one or more occurrences of p.
chainr1 :: ReadP r a -> ReadP r (a -> a -> a) -> ReadP r a Source #
Like chainr, but parses one or more occurrences of p.
manyTill :: ReadP r a -> ReadP [a] end -> ReadP r [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
readP_to_S :: ReadP a a -> ReadS a Source #
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 Source #
Converts a Haskell ReadS-style function into a parser. Warning: This introduces local backtracking in the resulting parser, and therefore a possible inefficiency.
Internal
Instances
| Monad (Parser r s) Source # | |
| Functor (Parser r s) Source # | |
| MonadFail (Parser r s) Source # | |
| Applicative (Parser r s) Source # | |
| s ~ Char => Alternative (Parser r s) Source # | |
| s ~ Char => MonadPlus (Parser r s) Source # | |
| t ~ Char => Parsing (Parser r t) Source # | |
| Methods try :: Parser r t a -> Parser r t a Source # (<?>) :: Parser r t a -> String -> Parser r t a Source # skipMany :: Parser r t a -> Parser r t () Source # skipSome :: Parser r t a -> Parser r t () Source # unexpected :: String -> Parser r t a Source # notFollowedBy :: Show a => Parser r t a -> Parser r t () Source # | |
| t ~ Char => CharParsing (Parser r t) Source # | |
| t ~ Char => CabalParsing (Parser r t) Source # | |