| Safe Haskell | Safe | 
|---|---|
| Language | Haskell98 | 
Text.ParserCombinators.Poly.Lex
Description
In a strict language, where creating the entire input list of tokens in one shot may be infeasible, we can use a lazy "callback" kind of architecture instead. The lexer returns a single token at a time, together with a continuation.
This module defines a Parser type (capable of use with the Poly combinators), specialised to the callback-lexer style of input stream.
Synopsis
- data LexReturn t
- newtype Parser t a = P (LexReturn t -> Result (LexReturn t) a)
- data Result z a
- runParser :: Parser t a -> LexReturn t -> (Either String a, String)
- next :: Parser t t
- eof :: Parser t ()
- satisfy :: (t -> Bool) -> Parser t t
- onFail :: Parser t a -> Parser t a -> Parser t a
- reparse :: [t] -> Parser t ()
- module Text.ParserCombinators.Poly.Base
- module Control.Applicative
The Parser datatype
In a strict language, where creating the entire input list of tokens
   in one shot may be infeasible, we can use a lazy "callback" kind of
   architecture instead.  The lexer returns a single token at a time,
   together with a continuation.  The next parser is responsible for 
   pulling on the token stream, applying the continuation where necessary.
This Parser datatype is a specialised parsing monad with error
   reporting.  This version is specialised to pre-lexed String input,
   where the lexer has been written to yield a LexReturn.
Instances
| Monad (Parser t) Source # | |
| Functor (Parser t) Source # | |
| MonadFail (Parser t) Source # | |
| Defined in Text.ParserCombinators.Poly.Lex | |
| Applicative (Parser t) Source # | |
| Alternative (Parser t) Source # | |
| PolyParse (Parser t) Source # | |
| Defined in Text.ParserCombinators.Poly.Lex | |
| Commitment (Parser t) Source # | |
A return type like Either, that distinguishes not only between right and wrong answers, but also has commitment, so that a failure cannot be undone. This should only be used for writing very primitive parsers - really it is an internal detail of the library. The z type is the remaining unconsumed input.
runParser :: Parser t a -> LexReturn t -> (Either String a, String) Source #
Apply a parser to an input token sequence.
Basic parsers
satisfy :: (t -> Bool) -> Parser t t Source #
Return the next token if it satisfies the given predicate.
onFail :: Parser t a -> Parser t a -> Parser t a infixl 6 Source #
p  means parse p, unless p fails, in which case
   parse q instead.
   Can be chained together to give multiple attempts to parse something.
   (Note that q could itself be a failing parser, e.g. to change the error
   message from that defined in p to something different.)
   However, a severe failure in p cannot be ignored.onFail q
Re-parsing
reparse :: [t] -> Parser t () Source #
Push some tokens back onto the front of the input stream and reparse. This is useful e.g. for recursively expanding macros. When the user-parser recognises a macro use, it can lookup the macro expansion from the parse state, lex it, and then stuff the lexed expansion back down into the parser.
Re-export all more general combinators
module Control.Applicative