polyparse-1.12.1: A variety of alternative parser combinator libraries.

Safe HaskellSafe
LanguageHaskell98

Text.ParserCombinators.Poly.Lex

Contents

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

The Parser datatype

data LexReturn t Source #

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.

Constructors

LexReturn t String (String -> LexReturn t) 
LexFinish 

newtype Parser t a Source #

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.

Constructors

P (LexReturn t -> Result (LexReturn t) a) 
Instances
Monad (Parser t) Source # 
Instance details

Defined in Text.ParserCombinators.Poly.Lex

Methods

(>>=) :: Parser t a -> (a -> Parser t b) -> Parser t b #

(>>) :: Parser t a -> Parser t b -> Parser t b #

return :: a -> Parser t a #

fail :: String -> Parser t a #

Functor (Parser t) Source # 
Instance details

Defined in Text.ParserCombinators.Poly.Lex

Methods

fmap :: (a -> b) -> Parser t a -> Parser t b #

(<$) :: a -> Parser t b -> Parser t a #

MonadFail (Parser t) Source # 
Instance details

Defined in Text.ParserCombinators.Poly.Lex

Methods

fail :: String -> Parser t a #

Applicative (Parser t) Source # 
Instance details

Defined in Text.ParserCombinators.Poly.Lex

Methods

pure :: a -> Parser t a #

(<*>) :: Parser t (a -> b) -> Parser t a -> Parser t b #

liftA2 :: (a -> b -> c) -> Parser t a -> Parser t b -> Parser t c #

(*>) :: Parser t a -> Parser t b -> Parser t b #

(<*) :: Parser t a -> Parser t b -> Parser t a #

Alternative (Parser t) Source # 
Instance details

Defined in Text.ParserCombinators.Poly.Lex

Methods

empty :: Parser t a #

(<|>) :: Parser t a -> Parser t a -> Parser t a #

some :: Parser t a -> Parser t [a] #

many :: Parser t a -> Parser t [a] #

PolyParse (Parser t) Source # 
Instance details

Defined in Text.ParserCombinators.Poly.Lex

Commitment (Parser t) Source # 
Instance details

Defined in Text.ParserCombinators.Poly.Lex

Methods

commit :: Parser t a -> Parser t a Source #

adjustErr :: Parser t a -> (String -> String) -> Parser t a Source #

oneOf' :: [(String, Parser t a)] -> Parser t a Source #

data Result z a 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.

Constructors

Success z a 
Failure z String 
Committed (Result z a) 
Instances
Functor (Result z) Source # 
Instance details

Defined in Text.ParserCombinators.Poly.Result

Methods

fmap :: (a -> b) -> Result z a -> Result z b #

(<$) :: a -> Result z b -> Result z a #

runParser :: Parser t a -> LexReturn t -> (Either String a, String) Source #

Apply a parser to an input token sequence.

Basic parsers

next :: Parser t t Source #

Simply return the next token in the input tokenstream.

eof :: Parser t () Source #

Succeed if the end of file/input has been reached, fail otherwise.

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 onFail q 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.

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