Safe Haskell | Safe |
---|---|
Language | Haskell98 |
Parser combinator framework.
Synopsis
- data Parser t e a = Parser ([t] -> ParseResult t e a)
- data ParseResult t e a
- = ParseSkip (Bag (Blocker t e))
- | ParseReturn (Bag (Blocker t e)) a
- | ParseFailure (Bag (Blocker t e))
- | ParseSuccess a [t]
- data Blocker t e = Blocker {
- blockerTokens :: [t]
- blockerExpected :: e
- parse :: Parser t e a -> [t] -> ParseResult t e a
- fail :: Parser t e a
- expected :: e -> Parser t e a
- commit :: Parser t e a -> Parser t e a
- enter :: (Bag (Blocker t e) -> e) -> Parser t e a -> Parser t e a
- enterOn :: Parser t e a -> (a -> Bag (Blocker t e) -> e) -> (a -> Parser t e b) -> Parser t e b
- peek :: Parser t e t
- item :: e -> Parser t e t
- satisfies :: e -> (t -> Bool) -> Parser t e t
- from :: e -> (t -> Maybe a) -> Parser t e a
- alt :: Parser t e a -> Parser t e a -> Parser t e a
- alts :: [Parser t e a] -> Parser t e a
- some :: Parser t e a -> Parser t e [a]
- many :: Parser t e a -> Parser t e [a]
- sepBy :: Parser t e a -> Parser t e s -> Parser t e [a]
- sepBy1 :: Parser t e a -> Parser t e s -> Parser t e [a]
- withDelims :: Parser t e a -> Parser t e (t, a, t)
Documentation
Parser is a function that takes a list of tokens, and returns a list of remaining tokens along with (on error) a list of descriptions of expected input, (on success) a parsed value.
Parser ([t] -> ParseResult t e a) |
data ParseResult t e a Source #
Result of a parser, parameterised by (t) the type of tokens, (e) the type for decriptions of what we're expecting to parse. (a) type of value to parse.
ParseSkip (Bag (Blocker t e)) | Parser failed after consuming no input. The parser looked at one or more tokens at the front of the input but based on these the input does not look like whatever syntax the parser was supposed to parse. |
ParseReturn (Bag (Blocker t e)) a | Parser yielding a value after consuming no input. The parser returned a value without looking at any tokens, this is a pure value returning action. |
ParseFailure (Bag (Blocker t e)) | Parse failed after partially consuming input. The parser thought that the input sequence looked like what it was supposed to parse, but complete parsing failed once it had committed. |
ParseSuccess a [t] | Parse succeeded yielding a value after consuming input. We have a complete value, and have consumed some input tokens. |
Instances
(Show t, Show e, Show a) => Show (ParseResult t e a) Source # | |
Defined in SMR.Source.Parsec showsPrec :: Int -> ParseResult t e a -> ShowS # show :: ParseResult t e a -> String # showList :: [ParseResult t e a] -> ShowS # |
Describes why the parser could not make further progress.
Blocker | |
|
parse :: Parser t e a -> [t] -> ParseResult t e a Source #
Apply a parser to a list of input tokens.
Always fail, producing no possible parses and no helpful error message.
expected :: e -> Parser t e a Source #
Always fail, yielding the given message describing what was expected.
commit :: Parser t e a -> Parser t e a Source #
Commit to the given parser, so if it skips or returns without consuming any input then treat that as failure.
enter :: (Bag (Blocker t e) -> e) -> Parser t e a -> Parser t e a Source #
Parse in an expectation context.
enterOn :: Parser t e a -> (a -> Bag (Blocker t e) -> e) -> (a -> Parser t e b) -> Parser t e b Source #
If the given parser suceeds then enter an expectation context for the next one.
satisfies :: e -> (t -> Bool) -> Parser t e t Source #
Consume the first input token if it matches the given predicate, failing without consuming if the predicate does not match.
from :: e -> (t -> Maybe a) -> Parser t e a Source #
Consume the first input token if it is accepted by the given match function. Fail without consuming if there is no match.
alt :: Parser t e a -> Parser t e a -> Parser t e a Source #
Given two parsers, try the first and if it succeeds produce the output of that parser, if not try the second.
alts :: [Parser t e a] -> Parser t e a Source #
Like alt
but take a list of parser, trying them in order.
some :: Parser t e a -> Parser t e [a] Source #
Parse zero or more things, yielding a list of those things.
many :: Parser t e a -> Parser t e [a] Source #
Parse one or more things, yielding a list of those things.
sepBy :: Parser t e a -> Parser t e s -> Parser t e [a] Source #
Parse some things separated by other things.
sepBy1 :: Parser t e a -> Parser t e s -> Parser t e [a] Source #
Parse at least one thing separated by other things.
withDelims :: Parser t e a -> Parser t e (t, a, t) Source #
Run a parser, peeking at the starting and ending tokens.