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

Safe HaskellSafe
LanguageHaskell98

Text.ParserCombinators.Poly.StateParser

Contents

Description

This module contains the definitions for a generic parser, with running state. These are the parts that are shared between the State and StateLazy variations. Do not import this module directly, but only via T.P.Poly.State or T.P.Poly.StateLazy.

Synopsis

The Parser datatype

newtype Parser s t a Source #

This Parser datatype is a fairly generic parsing monad with error reporting, and running state. It can be used for arbitrary token types, not just String input. (If you do not require a running state, use module Poly.Plain instead)

Constructors

P (s -> [t] -> Result ([t], s) a) 
Instances
Monad (Parser s t) Source # 
Instance details

Defined in Text.ParserCombinators.Poly.StateParser

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.StateParser

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.StateParser

Methods

fail :: String -> Parser s t a #

Applicative (Parser s t) Source # 
Instance details

Defined in Text.ParserCombinators.Poly.StateParser

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.StateParser

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.StateParser

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 #

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 #

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

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.