grammatical-parsers-0.3.1: parsers that combine into grammars

Safe HaskellNone
LanguageHaskell2010

Text.Grampa

Contents

Description

Collection of parsing algorithms with a common interface, operating on grammars represented as records with rank-2 field types.

Synopsis

Parsing methods

class MultiParsing m where Source #

Choose one of the instances of this class to parse with.

Minimal complete definition

parseComplete, parsePrefix

Associated Types

type ResultFunctor m :: * -> * Source #

Some parser types produce a single result, others a list of results.

type GrammarConstraint m (g :: (* -> *) -> *) :: Constraint Source #

Methods

parseComplete :: (GrammarConstraint m g, FactorialMonoid s) => g (m g s) -> s -> g (ResultFunctor m) Source #

Given a rank-2 record of parsers and input, produce a record of parses of the complete input.

parsePrefix :: (GrammarConstraint m g, FactorialMonoid s) => g (m g s) -> s -> g (Compose (ResultFunctor m) ((,) s)) Source #

Given a rank-2 record of parsers and input, produce a record of prefix parses paired with the remaining input suffix.

Instances

MultiParsing Parser Source #

Parallel parser produces a list of all possible parses.

parseComplete :: (Rank2.Functor g, FactorialMonoid s) =>
                 g (Parallel.Parser g s) -> s -> g (Compose ParseResults [])

Associated Types

type ResultFunctor (Parser :: ((* -> *) -> *) -> * -> * -> *) :: * -> * Source #

type GrammarConstraint (Parser :: ((* -> *) -> *) -> * -> * -> *) (g :: (* -> *) -> *) :: Constraint Source #

MultiParsing Parser Source #

Continuation-passing context-free parser

parseComplete :: (Rank2.Functor g, FactorialMonoid s) =>
                 g (Continued.Parser g s) -> s -> g ParseResults

Associated Types

type ResultFunctor (Parser :: ((* -> *) -> *) -> * -> * -> *) :: * -> * Source #

type GrammarConstraint (Parser :: ((* -> *) -> *) -> * -> * -> *) (g :: (* -> *) -> *) :: Constraint Source #

MultiParsing Parser Source #

Backtracking PEG parser

parseComplete :: (Rank2.Functor g, FactorialMonoid s) =>
                 g (Backtrack.Parser g s) -> s -> g ParseResults

Associated Types

type ResultFunctor (Parser :: ((* -> *) -> *) -> * -> * -> *) :: * -> * Source #

type GrammarConstraint (Parser :: ((* -> *) -> *) -> * -> * -> *) (g :: (* -> *) -> *) :: Constraint Source #

MultiParsing Parser Source #

Memoizing parser guarantees O(n²) performance for grammars with unambiguous productions, but provides no left recursion support.

parseComplete :: (Rank2.Functor g, FactorialMonoid s) =>
                 g (Memoizing.Parser g s) -> s -> g (Compose ParseResults [])

Associated Types

type ResultFunctor (Parser :: ((* -> *) -> *) -> * -> * -> *) :: * -> * Source #

type GrammarConstraint (Parser :: ((* -> *) -> *) -> * -> * -> *) (g :: (* -> *) -> *) :: Constraint Source #

MultiParsing Parser Source #

Memoizing parser guarantees O(n²) performance for grammars with unambiguous productions, but provides no left recursion support.

parseComplete :: (Rank2.Functor g, FactorialMonoid s) =>
                 g (Memoizing.Parser g s) -> s -> g (Compose ParseResults [])

Associated Types

type ResultFunctor (Parser :: ((* -> *) -> *) -> * -> * -> *) :: * -> * Source #

type GrammarConstraint (Parser :: ((* -> *) -> *) -> * -> * -> *) (g :: (* -> *) -> *) :: Constraint Source #

MultiParsing Parser Source #

Packrat parser

parseComplete :: (Rank2.Functor g, FactorialMonoid s) =>
                 g (Packrat.Parser g s) -> s -> g ParseResults

Associated Types

type ResultFunctor (Parser :: ((* -> *) -> *) -> * -> * -> *) :: * -> * Source #

type GrammarConstraint (Parser :: ((* -> *) -> *) -> * -> * -> *) (g :: (* -> *) -> *) :: Constraint Source #

MultiParsing (Fixed Parser) Source #

Parser of general context-free grammars, including left recursion.

parseComplete :: (Rank2.Apply g, Rank2.Traversable g, FactorialMonoid s) =>
                 g (LeftRecursive.'Fixed g s) -> s -> g (Compose ParseResults [])

Associated Types

type ResultFunctor (Fixed Parser :: ((* -> *) -> *) -> * -> * -> *) :: * -> * Source #

type GrammarConstraint (Fixed Parser :: ((* -> *) -> *) -> * -> * -> *) (g :: (* -> *) -> *) :: Constraint Source #

showFailure :: TextualMonoid s => s -> ParseFailure -> Int -> String Source #

Given the textual parse input, the parse failure on the input, and the number of lines preceding the failure to show, produce a human-readable failure description.

simply :: (Only r (p (Only r) s) -> s -> Only r f) -> p (Only r) s r -> s -> f r Source #

Apply the given parse function to the given grammar-free parser and its input.

Types

type Grammar (g :: (* -> *) -> *) p s = g (p g s) Source #

A type synonym for a fixed grammar record type g with a given parser type p on input streams of type s

type GrammarBuilder (g :: (* -> *) -> *) (g' :: (* -> *) -> *) (p :: ((* -> *) -> *) -> * -> * -> *) (s :: *) = g (p g' s) -> g (p g' s) Source #

A type synonym for an endomorphic function on a grammar record type g, whose parsers of type p build grammars of type g', parsing input streams of type s

data ParseFailure Source #

A ParseFailure contains the offset of the parse failure and the list of things expected at that offset.

Constructors

ParseFailure Int [String] 

newtype Ambiguous a Source #

An Ambiguous parse result, produced by the ambiguous combinator, contains a NonEmpty list of alternative results.

Constructors

Ambiguous (NonEmpty a) 

Instances

Functor Ambiguous Source # 

Methods

fmap :: (a -> b) -> Ambiguous a -> Ambiguous b #

(<$) :: a -> Ambiguous b -> Ambiguous a #

Show1 Ambiguous Source # 

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Ambiguous a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Ambiguous a] -> ShowS #

Eq a => Eq (Ambiguous a) Source # 

Methods

(==) :: Ambiguous a -> Ambiguous a -> Bool #

(/=) :: Ambiguous a -> Ambiguous a -> Bool #

Data a => Data (Ambiguous a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Ambiguous a -> c (Ambiguous a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Ambiguous a) #

toConstr :: Ambiguous a -> Constr #

dataTypeOf :: Ambiguous a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Ambiguous a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Ambiguous a)) #

gmapT :: (forall b. Data b => b -> b) -> Ambiguous a -> Ambiguous a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Ambiguous a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Ambiguous a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Ambiguous a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Ambiguous a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Ambiguous a -> m (Ambiguous a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Ambiguous a -> m (Ambiguous a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Ambiguous a -> m (Ambiguous a) #

Ord a => Ord (Ambiguous a) Source # 
Show a => Show (Ambiguous a) Source # 

Parser combinators and primitives

class MultiParsing m => GrammarParsing m where Source #

Parsers that belong to this class can memoize the parse results to avoid exponential performance complexity.

Minimal complete definition

nonTerminal

Associated Types

type GrammarFunctor m :: ((* -> *) -> *) -> * -> * -> * Source #

Methods

nonTerminal :: GrammarConstraint m g => (g (GrammarFunctor m g s) -> GrammarFunctor m g s a) -> m g s a Source #

Used to reference a grammar production, only necessary from outside the grammar itself

selfReferring :: (GrammarConstraint m g, Distributive g) => g (m g s) Source #

Construct a grammar whose every production refers to itself.

fixGrammar :: forall g s. (GrammarConstraint m g, Distributive g) => (g (m g s) -> g (m g s)) -> g (m g s) Source #

Convert a self-referring grammar function to a grammar.

recursive :: m g s a -> m g s a Source #

Mark a parser that relies on primitive recursion to prevent an infinite loop in fixGrammar.

Instances

GrammarParsing Parser Source # 

Associated Types

type GrammarFunctor (Parser :: ((* -> *) -> *) -> * -> * -> *) :: ((* -> *) -> *) -> * -> * -> * Source #

GrammarParsing Parser Source # 

Associated Types

type GrammarFunctor (Parser :: ((* -> *) -> *) -> * -> * -> *) :: ((* -> *) -> *) -> * -> * -> * Source #

GrammarParsing Parser Source # 

Associated Types

type GrammarFunctor (Parser :: ((* -> *) -> *) -> * -> * -> *) :: ((* -> *) -> *) -> * -> * -> * Source #

GrammarParsing (Fixed Parser) Source # 

Associated Types

type GrammarFunctor (Fixed Parser :: ((* -> *) -> *) -> * -> * -> *) :: ((* -> *) -> *) -> * -> * -> * Source #

class MonoidParsing m where Source #

Methods for parsing monoidal inputs

Methods

endOfInput :: FactorialMonoid s => m s () Source #

A parser that fails on any input and succeeds at its end.

getInput :: FactorialMonoid s => m s s Source #

Always sucessful parser that returns the remaining input without consuming it.

anyToken :: FactorialMonoid s => m s s Source #

A parser that accepts any single input atom.

satisfy :: FactorialMonoid s => (s -> Bool) -> m s s Source #

A parser that accepts an input atom only if it satisfies the given predicate.

satisfyChar :: TextualMonoid s => (Char -> Bool) -> m s Char Source #

Specialization of satisfy on TextualMonoid inputs, accepting and returning an input character only if it satisfies the given predicate.

satisfyCharInput :: TextualMonoid s => (Char -> Bool) -> m s s Source #

Specialization of satisfy on TextualMonoid inputs, accepting an input character only if it satisfies the given predicate, and returning the input atom that represents the character. A faster version of singleton $ satisfyChar p and of satisfy (fromMaybe False p . characterPrefix).

notSatisfy :: FactorialMonoid s => (s -> Bool) -> m s () Source #

A parser that succeeds exactly when satisfy doesn't, equivalent to notFollowedBy . satisfy

notSatisfyChar :: TextualMonoid s => (Char -> Bool) -> m s () Source #

A parser that succeeds exactly when satisfyChar doesn't, equivalent to notFollowedBy . satisfyChar

scan :: FactorialMonoid t => s -> (s -> t -> Maybe s) -> m t t Source #

A stateful scanner. The predicate modifies a state argument, and each transformed state is passed to successive invocations of the predicate on each token of the input until one returns Nothing or the input ends.

This parser does not fail. It will return an empty string if the predicate returns Nothing on the first character.

Note: Because this parser does not fail, do not use it with combinators such as many, because such parsers loop until a failure occurs. Careless use will thus result in an infinite loop.

scanChars :: TextualMonoid t => s -> (s -> Char -> Maybe s) -> m t t Source #

Stateful scanner like scanChars, but specialized for TextualMonoid inputs.

string :: (FactorialMonoid s, LeftReductiveMonoid s, Show s) => s -> m s s Source #

A parser that consumes and returns the given prefix of the input.

takeWhile :: FactorialMonoid s => (s -> Bool) -> m s s Source #

A parser accepting the longest sequence of input atoms that match the given predicate; an optimized version of 'concatMany . satisfy'.

Note: Because this parser does not fail, do not use it with combinators such as many, because such parsers loop until a failure occurs. Careless use will thus result in an infinite loop.

takeWhile1 :: FactorialMonoid s => (s -> Bool) -> m s s Source #

A parser accepting the longest non-empty sequence of input atoms that match the given predicate; an optimized version of 'concatSome . satisfy'.

takeCharsWhile :: TextualMonoid s => (Char -> Bool) -> m s s Source #

Specialization of takeWhile on TextualMonoid inputs, accepting the longest sequence of input characters that match the given predicate; an optimized version of 'fmap fromString . many . satisfyChar'.

Note: Because this parser does not fail, do not use it with combinators such as many, because such parsers loop until a failure occurs. Careless use will thus result in an infinite loop.

takeCharsWhile1 :: TextualMonoid s => (Char -> Bool) -> m s s Source #

Specialization of takeWhile1 on TextualMonoid inputs, accepting the longest sequence of input characters that match the given predicate; an optimized version of 'fmap fromString . some . satisfyChar'.

concatMany :: Monoid a => m s a -> m s a Source #

Zero or more argument occurrences like many, with concatenated monoidal results.

concatMany :: (Monoid a, Alternative (m s)) => m s a -> m s a Source #

Zero or more argument occurrences like many, with concatenated monoidal results.

Instances

MonoidParsing (Parser g) Source # 

Methods

endOfInput :: FactorialMonoid s => Parser g s () Source #

getInput :: FactorialMonoid s => Parser g s s Source #

anyToken :: FactorialMonoid s => Parser g s s Source #

satisfy :: FactorialMonoid s => (s -> Bool) -> Parser g s s Source #

satisfyChar :: TextualMonoid s => (Char -> Bool) -> Parser g s Char Source #

satisfyCharInput :: TextualMonoid s => (Char -> Bool) -> Parser g s s Source #

notSatisfy :: FactorialMonoid s => (s -> Bool) -> Parser g s () Source #

notSatisfyChar :: TextualMonoid s => (Char -> Bool) -> Parser g s () Source #

scan :: FactorialMonoid t => s -> (s -> t -> Maybe s) -> Parser g t t Source #

scanChars :: TextualMonoid t => s -> (s -> Char -> Maybe s) -> Parser g t t Source #

string :: (FactorialMonoid s, LeftReductiveMonoid s, Show s) => s -> Parser g s s Source #

takeWhile :: FactorialMonoid s => (s -> Bool) -> Parser g s s Source #

takeWhile1 :: FactorialMonoid s => (s -> Bool) -> Parser g s s Source #

takeCharsWhile :: TextualMonoid s => (Char -> Bool) -> Parser g s s Source #

takeCharsWhile1 :: TextualMonoid s => (Char -> Bool) -> Parser g s s Source #

concatMany :: Monoid a => Parser g s a -> Parser g s a Source #

MonoidParsing (Parser g) Source # 

Methods

endOfInput :: FactorialMonoid s => Parser g s () Source #

getInput :: FactorialMonoid s => Parser g s s Source #

anyToken :: FactorialMonoid s => Parser g s s Source #

satisfy :: FactorialMonoid s => (s -> Bool) -> Parser g s s Source #

satisfyChar :: TextualMonoid s => (Char -> Bool) -> Parser g s Char Source #

satisfyCharInput :: TextualMonoid s => (Char -> Bool) -> Parser g s s Source #

notSatisfy :: FactorialMonoid s => (s -> Bool) -> Parser g s () Source #

notSatisfyChar :: TextualMonoid s => (Char -> Bool) -> Parser g s () Source #

scan :: FactorialMonoid t => s -> (s -> t -> Maybe s) -> Parser g t t Source #

scanChars :: TextualMonoid t => s -> (s -> Char -> Maybe s) -> Parser g t t Source #

string :: (FactorialMonoid s, LeftReductiveMonoid s, Show s) => s -> Parser g s s Source #

takeWhile :: FactorialMonoid s => (s -> Bool) -> Parser g s s Source #

takeWhile1 :: FactorialMonoid s => (s -> Bool) -> Parser g s s Source #

takeCharsWhile :: TextualMonoid s => (Char -> Bool) -> Parser g s s Source #

takeCharsWhile1 :: TextualMonoid s => (Char -> Bool) -> Parser g s s Source #

concatMany :: Monoid a => Parser g s a -> Parser g s a Source #

MonoidParsing (Parser g) Source # 

Methods

endOfInput :: FactorialMonoid s => Parser g s () Source #

getInput :: FactorialMonoid s => Parser g s s Source #

anyToken :: FactorialMonoid s => Parser g s s Source #

satisfy :: FactorialMonoid s => (s -> Bool) -> Parser g s s Source #

satisfyChar :: TextualMonoid s => (Char -> Bool) -> Parser g s Char Source #

satisfyCharInput :: TextualMonoid s => (Char -> Bool) -> Parser g s s Source #

notSatisfy :: FactorialMonoid s => (s -> Bool) -> Parser g s () Source #

notSatisfyChar :: TextualMonoid s => (Char -> Bool) -> Parser g s () Source #

scan :: FactorialMonoid t => s -> (s -> t -> Maybe s) -> Parser g t t Source #

scanChars :: TextualMonoid t => s -> (s -> Char -> Maybe s) -> Parser g t t Source #

string :: (FactorialMonoid s, LeftReductiveMonoid s, Show s) => s -> Parser g s s Source #

takeWhile :: FactorialMonoid s => (s -> Bool) -> Parser g s s Source #

takeWhile1 :: FactorialMonoid s => (s -> Bool) -> Parser g s s Source #

takeCharsWhile :: TextualMonoid s => (Char -> Bool) -> Parser g s s Source #

takeCharsWhile1 :: TextualMonoid s => (Char -> Bool) -> Parser g s s Source #

concatMany :: Monoid a => Parser g s a -> Parser g s a Source #

MonoidParsing (Parser g) Source # 

Methods

endOfInput :: FactorialMonoid s => Parser g s () Source #

getInput :: FactorialMonoid s => Parser g s s Source #

anyToken :: FactorialMonoid s => Parser g s s Source #

satisfy :: FactorialMonoid s => (s -> Bool) -> Parser g s s Source #

satisfyChar :: TextualMonoid s => (Char -> Bool) -> Parser g s Char Source #

satisfyCharInput :: TextualMonoid s => (Char -> Bool) -> Parser g s s Source #

notSatisfy :: FactorialMonoid s => (s -> Bool) -> Parser g s () Source #

notSatisfyChar :: TextualMonoid s => (Char -> Bool) -> Parser g s () Source #

scan :: FactorialMonoid t => s -> (s -> t -> Maybe s) -> Parser g t t Source #

scanChars :: TextualMonoid t => s -> (s -> Char -> Maybe s) -> Parser g t t Source #

string :: (FactorialMonoid s, LeftReductiveMonoid s, Show s) => s -> Parser g s s Source #

takeWhile :: FactorialMonoid s => (s -> Bool) -> Parser g s s Source #

takeWhile1 :: FactorialMonoid s => (s -> Bool) -> Parser g s s Source #

takeCharsWhile :: TextualMonoid s => (Char -> Bool) -> Parser g s s Source #

takeCharsWhile1 :: TextualMonoid s => (Char -> Bool) -> Parser g s s Source #

concatMany :: Monoid a => Parser g s a -> Parser g s a Source #

MonoidParsing (Parser g) Source # 

Methods

endOfInput :: FactorialMonoid s => Parser g s () Source #

getInput :: FactorialMonoid s => Parser g s s Source #

anyToken :: FactorialMonoid s => Parser g s s Source #

satisfy :: FactorialMonoid s => (s -> Bool) -> Parser g s s Source #

satisfyChar :: TextualMonoid s => (Char -> Bool) -> Parser g s Char Source #

satisfyCharInput :: TextualMonoid s => (Char -> Bool) -> Parser g s s Source #

notSatisfy :: FactorialMonoid s => (s -> Bool) -> Parser g s () Source #

notSatisfyChar :: TextualMonoid s => (Char -> Bool) -> Parser g s () Source #

scan :: FactorialMonoid t => s -> (s -> t -> Maybe s) -> Parser g t t Source #

scanChars :: TextualMonoid t => s -> (s -> Char -> Maybe s) -> Parser g t t Source #

string :: (FactorialMonoid s, LeftReductiveMonoid s, Show s) => s -> Parser g s s Source #

takeWhile :: FactorialMonoid s => (s -> Bool) -> Parser g s s Source #

takeWhile1 :: FactorialMonoid s => (s -> Bool) -> Parser g s s Source #

takeCharsWhile :: TextualMonoid s => (Char -> Bool) -> Parser g s s Source #

takeCharsWhile1 :: TextualMonoid s => (Char -> Bool) -> Parser g s s Source #

concatMany :: Monoid a => Parser g s a -> Parser g s a Source #

MonoidParsing (Parser g) Source # 

Methods

endOfInput :: FactorialMonoid s => Parser g s () Source #

getInput :: FactorialMonoid s => Parser g s s Source #

anyToken :: FactorialMonoid s => Parser g s s Source #

satisfy :: FactorialMonoid s => (s -> Bool) -> Parser g s s Source #

satisfyChar :: TextualMonoid s => (Char -> Bool) -> Parser g s Char Source #

satisfyCharInput :: TextualMonoid s => (Char -> Bool) -> Parser g s s Source #

notSatisfy :: FactorialMonoid s => (s -> Bool) -> Parser g s () Source #

notSatisfyChar :: TextualMonoid s => (Char -> Bool) -> Parser g s () Source #

scan :: FactorialMonoid t => s -> (s -> t -> Maybe s) -> Parser g t t Source #

scanChars :: TextualMonoid t => s -> (s -> Char -> Maybe s) -> Parser g t t Source #

string :: (FactorialMonoid s, LeftReductiveMonoid s, Show s) => s -> Parser g s s Source #

takeWhile :: FactorialMonoid s => (s -> Bool) -> Parser g s s Source #

takeWhile1 :: FactorialMonoid s => (s -> Bool) -> Parser g s s Source #

takeCharsWhile :: TextualMonoid s => (Char -> Bool) -> Parser g s s Source #

takeCharsWhile1 :: TextualMonoid s => (Char -> Bool) -> Parser g s s Source #

concatMany :: Monoid a => Parser g s a -> Parser g s a Source #

MonoidParsing (Fixed Parser g) Source # 

class AmbiguousParsing m where Source #

Parsers that can produce alternative parses and collect them into an Ambiguous node

Minimal complete definition

ambiguous

Methods

ambiguous :: m a -> m (Ambiguous a) Source #

Collect all alternative parses of the same length into a NonEmpty list of results.

Instances

class Lexical (g :: (* -> *) -> *) where Source #

If a grammar is Lexical, its parsers can instantiate the TokenParsing class.

Associated Types

type LexicalConstraint (m :: ((* -> *) -> *) -> * -> * -> *) g s :: Constraint Source #

Methods

lexicalWhiteSpace :: LexicalConstraint m g s => m g s () Source #

Always succeeds, consuming all white space and comments

someLexicalSpace :: LexicalConstraint m g s => m g s () Source #

Consumes all whitespace and comments, failing if there are none

lexicalComment :: LexicalConstraint m g s => m g s () Source #

Consumes a single comment, defaults to empty

lexicalSemicolon :: LexicalConstraint m g s => m g s Char Source #

Consumes a single semicolon and any trailing whitespace, returning the character |';'|. The method can be overridden for automatic semicolon insertion, but if it succeeds on semicolon or white space input it must consume it.

lexicalToken :: LexicalConstraint m g s => m g s a -> m g s a Source #

Applies the argument parser and consumes the trailing lexicalWhitespace

identifierToken :: LexicalConstraint m g s => m g s s -> m g s s Source #

Applies the argument parser, determines whether its result is a legal identifier, and consumes the trailing lexicalWhitespace

isIdentifierStartChar :: Char -> Bool Source #

Determines whether the given character can start an identifier token, allows only a letter or underscore by default

isIdentifierFollowChar :: Char -> Bool Source #

Determines whether the given character can be any part of an identifier token, also allows numbers

identifier :: LexicalConstraint m g s => m g s s Source #

Parses a valid identifier and consumes the trailing lexicalWhitespace

keyword :: LexicalConstraint m g s => s -> m g s () Source #

Parses the argument word whole, not followed by any identifier character, and consumes the trailing lexicalWhitespace

lexicalComment :: Alternative (m g s) => m g s () Source #

Consumes a single comment, defaults to empty

lexicalWhiteSpace :: (LexicalConstraint m g s, Parsing (m g s), MonoidParsing (m g), TextualMonoid s) => m g s () Source #

Always succeeds, consuming all white space and comments

someLexicalSpace :: (LexicalConstraint m g s, Parsing (m g s), MonoidParsing (m g), TextualMonoid s) => m g s () Source #

Consumes all whitespace and comments, failing if there are none

lexicalSemicolon :: (LexicalConstraint m g s, CharParsing (m g s), MonoidParsing (m g), TextualMonoid s) => m g s Char Source #

Consumes a single semicolon and any trailing whitespace, returning the character |';'|. The method can be overridden for automatic semicolon insertion, but if it succeeds on semicolon or white space input it must consume it.

lexicalToken :: (LexicalConstraint m g s, Parsing (m g s), MonoidParsing (m g), TextualMonoid s) => m g s a -> m g s a Source #

Applies the argument parser and consumes the trailing lexicalWhitespace

identifierToken :: (LexicalConstraint m g s, Parsing (m g s), MonoidParsing (m g), TextualMonoid s) => m g s s -> m g s s Source #

Applies the argument parser, determines whether its result is a legal identifier, and consumes the trailing lexicalWhitespace

identifier :: (LexicalConstraint m g s, Monad (m g s), Alternative (m g s), Parsing (m g s), MonoidParsing (m g), TextualMonoid s) => m g s s Source #

Parses a valid identifier and consumes the trailing lexicalWhitespace

keyword :: (LexicalConstraint m g s, Parsing (m g s), MonoidParsing (m g), Show s, TextualMonoid s) => s -> m g s () Source #

Parses the argument word whole, not followed by any identifier character, and consumes the trailing lexicalWhitespace