Safe Haskell | Safe |
---|---|
Language | Haskell98 |
This library of monadic parser combinators is based on the ones
defined by Graham Hutton and Erik Meijer. It has been extended by
Malcolm Wallace to use an abstract token type (no longer just a
string) as input, and to incorporate state in the monad, useful
for symbol tables, macros, and so on. Basic facilities for error
reporting have also been added, and later extended by Graham Klyne
to return the errors through an Either
type, rather than just
calling error
.
Synopsis
- newtype Parser s t e a = P (s -> [Either e t] -> ParseResult s t e a)
- item :: Parser s t e t
- eof :: Show p => Parser s (p, t) String ()
- papply :: Parser s t String a -> s -> [Either String t] -> [(a, s, [Either String t])]
- papply' :: Parser s t e a -> s -> [Either e t] -> Either e [(a, s, [Either e t])]
- (+++) :: Parser s t e a -> Parser s t e a -> Parser s t e a
- tok :: Eq t => t -> Parser s (p, t) e t
- nottok :: Eq t => [t] -> Parser s (p, t) e t
- many :: Parser s t e a -> Parser s t e [a]
- many1 :: Parser s t e a -> Parser s t e [a]
- sepby :: Parser s t e a -> Parser s t e b -> Parser s t e [a]
- sepby1 :: Parser s t e a -> Parser s t e b -> Parser s t e [a]
- chainl :: Parser s t e a -> Parser s t e (a -> a -> a) -> a -> Parser s t e a
- chainl1 :: Parser s t e a -> Parser s t e (a -> a -> a) -> Parser s t e a
- chainr :: Parser s t e a -> Parser s t e (a -> a -> a) -> a -> Parser s t e a
- chainr1 :: Parser s t e a -> Parser s t e (a -> a -> a) -> Parser s t e a
- ops :: [(Parser s t e a, b)] -> Parser s t e b
- bracket :: (Show p, Show t) => Parser s (p, t) e a -> Parser s (p, t) e b -> Parser s (p, t) e c -> Parser s (p, t) e b
- toEOF :: Show p => Parser s (p, t) String a -> Parser s (p, t) String a
- elserror :: (Show p, Show t) => Parser s (p, t) String a -> String -> Parser s (p, t) String a
- stupd :: (s -> s) -> Parser s t e ()
- stquery :: (s -> a) -> Parser s t e a
- stget :: Parser s t e s
- reparse :: [Either e t] -> Parser s t e ()
The parser monad
newtype Parser s t e a Source #
P (s -> [Either e t] -> ParseResult s t e a) | The parser type is parametrised on the types of the state |
Instances
Monad (Parser s t e) Source # | |
Functor (Parser s t e) Source # | |
MonadFail (Parser s t e) Source # | |
Defined in Text.ParserCombinators.HuttonMeijerWallace | |
Applicative (Parser s t e) Source # | |
Defined in Text.ParserCombinators.HuttonMeijerWallace | |
Alternative (Parser s t e) Source # | |
MonadPlus (Parser s t e) Source # | |
Primitive parser combinators
papply :: Parser s t String a -> s -> [Either String t] -> [(a, s, [Either String t])] Source #
Apply the parser to some real input, given an initial state value.
If the parser fails, raise error
to halt the program.
(This is the original exported behaviour - to allow the caller to
deal with the error differently, see papply'
.)
papply' :: Parser s t e a -> s -> [Either e t] -> Either e [(a, s, [Either e t])] Source #
Apply the parser to some real input, given an initial state value. If the parser fails, return a diagnostic message to the caller.
Derived combinators
(+++) :: Parser s t e a -> Parser s t e a -> Parser s t e a infixr 5 Source #
A choice between parsers. Keep only the first success.
nottok :: Eq t => [t] -> Parser s (p, t) e t Source #
Deliver the first token if it does not equal the argument.
sepby :: Parser s t e a -> Parser s t e b -> Parser s t e [a] Source #
Deliver zero or more values of a
separated by b
's.
sepby1 :: Parser s t e a -> Parser s t e b -> Parser s t e [a] Source #
Deliver one or more values of a
separated by b
's.
bracket :: (Show p, Show t) => Parser s (p, t) e a -> Parser s (p, t) e b -> Parser s (p, t) e c -> Parser s (p, t) e b Source #
toEOF :: Show p => Parser s (p, t) String a -> Parser s (p, t) String a Source #
Accept a complete parse of the input only, no partial parses.
Error handling
elserror :: (Show p, Show t) => Parser s (p, t) String a -> String -> Parser s (p, t) String a Source #
If the parser fails, generate an error message.