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

Safe HaskellNone
LanguageHaskell98

Text.ParserCombinators.Poly.StateLazy

Contents

Synopsis

The Parser datatype

newtype Parser s t a Source #

The only differences between a State and a StateLazy parser are the instance of Applicative, and the type (and implementation) of runParser. We therefore need to newtype the original Parser type, to allow it to have a different instance.

Constructors

P (Parser s t a) 
Instances
Monad (Parser s t) Source # 
Instance details

Defined in Text.ParserCombinators.Poly.StateLazy

Methods

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

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

return :: a -> Parser s t a #

fail :: String -> Parser s t a #

Functor (Parser s t) Source # 
Instance details

Defined in Text.ParserCombinators.Poly.StateLazy

Methods

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

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

MonadFail (Parser s t) Source # 
Instance details

Defined in Text.ParserCombinators.Poly.StateLazy

Methods

fail :: String -> Parser s t a #

Applicative (Parser s t) Source # 
Instance details

Defined in Text.ParserCombinators.Poly.StateLazy

Methods

pure :: a -> Parser s t a #

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

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

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

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

Alternative (Parser s t) Source # 
Instance details

Defined in Text.ParserCombinators.Poly.StateLazy

Methods

empty :: Parser s t a #

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

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

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

PolyParse (Parser s t) Source # 
Instance details

Defined in Text.ParserCombinators.Poly.StateLazy

Commitment (Parser s t) Source # 
Instance details

Defined in Text.ParserCombinators.Poly.StateLazy

Methods

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

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

oneOf' :: [(String, Parser s t a)] -> Parser s 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 s t a -> s -> [t] -> (a, s, [t]) Source #

Apply a parser to an input token sequence.

Basic parsers

next :: Parser s t t Source #

Simply return the next token in the input tokenstream.

eof :: Parser s t () Source #

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

satisfy :: (t -> Bool) -> Parser s t t Source #

Return the next token if it satisfies the given predicate.

onFail :: Parser s t a -> Parser s t a -> Parser s t a 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.

manyFinally :: Parser s t a -> Parser s t z -> Parser s t [a] Source #

State-handling

stUpdate :: (s -> s) -> Parser s t () Source #

Update the internal state.

stQuery :: (s -> a) -> Parser s t a Source #

Query the internal state.

stGet :: Parser s t s Source #

Deliver the entire internal state.

Re-parsing

reparse :: [t] -> Parser s 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

class (Functor p, Monad p, MonadFail p, Applicative p, Alternative p, Commitment p) => PolyParse p Source #

The PolyParse class is an abstraction gathering all of the common features that a two-level error-handling parser requires: the applicative parsing interface, the monadic interface, and commitment.

There are two additional basic combinators that we expect to be implemented afresh for every concrete type, but which (for technical reasons) cannot be class methods. They are next and satisfy.

class Commitment p where Source #

The Commitment class is an abstraction over all the current concrete representations of monadic/applicative parser combinators in this package. The common feature is two-level error-handling. Some primitives must be implemented specific to each parser type (e.g. depending on whether the parser has a running state, or whether it is lazy). But given those primitives, large numbers of combinators do not depend any further on the internal structure of the particular parser.

Methods

commit :: p a -> p a Source #

Commit is a way of raising the severity of any errors found within its argument. Used in the middle of a parser definition, it means that any operations prior to commitment fail softly, but after commitment, they fail hard.

adjustErr :: p a -> (String -> String) -> p a Source #

p adjustErr f applies the transformation f to any error message generated in p, having no effect if p succeeds.

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

Parse the first alternative that succeeds, but if none succeed, report only the severe errors, and if none of those, then report all the soft errors.

Instances
Commitment Parser Source # 
Instance details

Defined in Text.ParserCombinators.Poly.ByteStringChar

Methods

commit :: Parser a -> Parser a Source #

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

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

Commitment Parser Source # 
Instance details

Defined in Text.ParserCombinators.Poly.ByteString

Methods

commit :: Parser a -> Parser a Source #

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

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

Commitment Parser Source # 
Instance details

Defined in Text.ParserCombinators.Poly.Text

Methods

commit :: Parser a -> Parser a Source #

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

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

Commitment (Parser t) Source # 
Instance details

Defined in Text.ParserCombinators.Poly.Parser

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 #

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 #

Commitment (Parser t) Source # 
Instance details

Defined in Text.ParserCombinators.Poly.Lazy

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 #

Commitment (Parser s) Source # 
Instance details

Defined in Text.ParserCombinators.Poly.StateText

Methods

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

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

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

Commitment (Parser s t) Source # 
Instance details

Defined in Text.ParserCombinators.Poly.StateParser

Methods

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

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

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

Commitment (Parser s t) Source # 
Instance details

Defined in Text.ParserCombinators.Poly.StateLazy

Methods

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

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

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

apply :: PolyParse p => p (a -> b) -> p a -> p b infixl 3 Source #

Apply a parsed function to a parsed value. Rather like ordinary function application lifted into parsers.

discard :: PolyParse p => p a -> p b -> p a infixl 3 Source #

x discard y parses both x and y, but discards the result of y. Rather like const lifted into parsers.

failBad :: PolyParse p => String -> p a Source #

When a simple fail is not strong enough, use failBad for emphasis. An emphasised (severe) error cannot be overridden by choice operators.

adjustErrBad :: PolyParse p => p a -> (String -> String) -> p a Source #

adjustErrBad is just like adjustErr except it also raises the severity of the error.

oneOf :: PolyParse p => [p a] -> p a Source #

Parse the first alternative in the list that succeeds.

indent :: Int -> String -> String Source #

Helper for formatting error messages: indents all lines by a fixed amount.

exactly :: PolyParse p => Int -> p a -> p [a] Source #

'exactly n p' parses precisely n items, using the parser p, in sequence.

upto :: PolyParse p => Int -> p a -> p [a] Source #

'upto n p' parses n or fewer items, using the parser p, in sequence.

many1 :: PolyParse p => p a -> p [a] Source #

Parse a non-empty list of items.

sepBy :: PolyParse p => p a -> p sep -> p [a] Source #

Parse a list of items separated by discarded junk.

sepBy1 :: PolyParse p => p a -> p sep -> p [a] Source #

Parse a non-empty list of items separated by discarded junk.

bracketSep :: PolyParse p => p bra -> p sep -> p ket -> p a -> p [a] Source #

Parse a list of items, discarding the start, end, and separator items.

bracket :: PolyParse p => p bra -> p ket -> p a -> p a Source #

Parse a bracketed item, discarding the brackets. If everything matches except the closing bracket, the whole parse fails soft, which can give less-than-satisfying error messages. If you want better error messages, try calling with e.g. bracket open (commit close) item

manyFinally' :: (PolyParse p, Show a) => p a -> p z -> p [a] Source #

manyFinally' is like manyFinally, except when the terminator parser overlaps with the element parser. In manyFinally e t, the parser t is tried only when parser e fails, whereas in manyFinally' e t, the parser t is always tried first, then parser e only if the terminator is not found. For instance, manyFinally (accept "01") (accept "0") on input "0101010" returns ["01","01","01"], whereas manyFinally' with the same arguments and input returns [].