grammatical-parsers-0.4.0.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.

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 [])
Instance details

Defined in Text.Grampa.ContextFree.Parallel

MultiParsing Parser Source #

Continuation-passing context-free parser

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

Defined in Text.Grampa.ContextFree.Continued

MultiParsing Parser Source #

Backtracking PEG parser

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

Defined in Text.Grampa.PEG.Backtrack

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 [])
Instance details

Defined in Text.Grampa.ContextFree.SortedMemoizing

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 [])
Instance details

Defined in Text.Grampa.ContextFree.Memoizing

MultiParsing Parser Source #

Packrat parser

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

Defined in Text.Grampa.PEG.Packrat

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 [])
Instance details

Defined in Text.Grampa.ContextFree.LeftRecursive

offsetContext :: (Eq s, IsString s, FactorialMonoid s) => s -> Int -> Int -> s Source #

Given the parser input, an offset within it, and desired number of context lines, returns a description of the offset position in English.

offsetLineAndColumn :: (Eq s, IsString s, FactorialMonoid s) => s -> Int -> ([s], Int) Source #

Given the full input and an offset within it, returns all the input lines up to and including the offset in reverse order, as well as the zero-based column number of the offset

positionOffset :: FactorialMonoid s => s -> Position s -> Int Source #

Map the position into its offset from the beginning of the full input.

failureDescription :: forall s. (Eq s, IsString s, FactorialMonoid s) => s -> ParseFailure -> Int -> s 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] 
Instances
Eq ParseFailure Source # 
Instance details

Defined in Text.Grampa.Class

Show ParseFailure Source # 
Instance details

Defined in Text.Grampa.Class

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 # 
Instance details

Defined in Text.Grampa.Class

Methods

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

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

Applicative Ambiguous Source # 
Instance details

Defined in Text.Grampa.Class

Methods

pure :: a -> Ambiguous a #

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

liftA2 :: (a -> b -> c) -> Ambiguous a -> Ambiguous b -> Ambiguous c #

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

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

Foldable Ambiguous Source # 
Instance details

Defined in Text.Grampa.Class

Methods

fold :: Monoid m => Ambiguous m -> m #

foldMap :: Monoid m => (a -> m) -> Ambiguous a -> m #

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

foldr' :: (a -> b -> b) -> b -> Ambiguous a -> b #

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

foldl' :: (b -> a -> b) -> b -> Ambiguous a -> b #

foldr1 :: (a -> a -> a) -> Ambiguous a -> a #

foldl1 :: (a -> a -> a) -> Ambiguous a -> a #

toList :: Ambiguous a -> [a] #

null :: Ambiguous a -> Bool #

length :: Ambiguous a -> Int #

elem :: Eq a => a -> Ambiguous a -> Bool #

maximum :: Ord a => Ambiguous a -> a #

minimum :: Ord a => Ambiguous a -> a #

sum :: Num a => Ambiguous a -> a #

product :: Num a => Ambiguous a -> a #

Traversable Ambiguous Source # 
Instance details

Defined in Text.Grampa.Class

Methods

traverse :: Applicative f => (a -> f b) -> Ambiguous a -> f (Ambiguous b) #

sequenceA :: Applicative f => Ambiguous (f a) -> f (Ambiguous a) #

mapM :: Monad m => (a -> m b) -> Ambiguous a -> m (Ambiguous b) #

sequence :: Monad m => Ambiguous (m a) -> m (Ambiguous a) #

Show1 Ambiguous Source # 
Instance details

Defined in Text.Grampa.Class

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 # 
Instance details

Defined in Text.Grampa.Class

Methods

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

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

Data a => Data (Ambiguous a) Source # 
Instance details

Defined in Text.Grampa.Class

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 # 
Instance details

Defined in Text.Grampa.Class

Show a => Show (Ambiguous a) Source # 
Instance details

Defined in Text.Grampa.Class

Semigroup a => Semigroup (Ambiguous a) Source # 
Instance details

Defined in Text.Grampa.Class

Methods

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

sconcat :: NonEmpty (Ambiguous a) -> Ambiguous a #

stimes :: Integral b => b -> Ambiguous a -> Ambiguous a #

Monoid a => Monoid (Ambiguous a) Source # 
Instance details

Defined in Text.Grampa.Class

data Position s Source #

Opaque data type that represents an input position.

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 # 
Instance details

Defined in Text.Grampa.ContextFree.SortedMemoizing

Associated Types

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

GrammarParsing Parser Source # 
Instance details

Defined in Text.Grampa.ContextFree.Memoizing

Associated Types

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

GrammarParsing Parser Source # 
Instance details

Defined in Text.Grampa.PEG.Packrat

Associated Types

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

GrammarParsing (Fixed Parser) Source # 
Instance details

Defined in Text.Grampa.ContextFree.LeftRecursive

Associated Types

type GrammarFunctor (Fixed Parser) :: ((Type -> Type) -> Type) -> Type -> Type -> Type 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.

getSourcePos :: FactorialMonoid s => m s (Position s) Source #

Retrieve the Position the parser has reached in the input source.

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

getSourcePos :: (FactorialMonoid s, Functor (m s)) => m s (Position s) Source #

Retrieve the Position the parser has reached in the input source.

Instances
MonoidParsing (Parser g) Source # 
Instance details

Defined in Text.Grampa.ContextFree.Parallel

MonoidParsing (Parser g) Source # 
Instance details

Defined in Text.Grampa.ContextFree.Continued

MonoidParsing (Parser g) Source # 
Instance details

Defined in Text.Grampa.PEG.Backtrack

MonoidParsing (Parser g) Source # 
Instance details

Defined in Text.Grampa.ContextFree.SortedMemoizing

MonoidParsing (Parser g) Source # 
Instance details

Defined in Text.Grampa.ContextFree.Memoizing

MonoidParsing (Parser g) Source # 
Instance details

Defined in Text.Grampa.PEG.Packrat

MonoidParsing (Fixed Parser g) Source # 
Instance details

Defined in Text.Grampa.ContextFree.LeftRecursive

class AmbiguousParsing m where Source #

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

Methods

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

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

Instances
AmbiguousParsing (Parser g s) Source # 
Instance details

Defined in Text.Grampa.ContextFree.SortedMemoizing

Methods

ambiguous :: Parser g s a -> Parser g s (Ambiguous a) Source #

AmbiguousParsing (Fixed Parser g s) Source # 
Instance details

Defined in Text.Grampa.ContextFree.LeftRecursive

Methods

ambiguous :: Fixed Parser g s a -> Fixed Parser g s (Ambiguous a) Source #

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

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

Minimal complete definition

Nothing

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

class Parsing m => CharParsing (m :: Type -> Type) where #

Additional functionality needed to parse character streams.

Minimal complete definition

Nothing

Methods

char :: Char -> m Char #

char c parses a single character c. Returns the parsed character (i.e. c).

e.g.

semiColon = char ';'

notChar :: Char -> m Char #

notChar c parses any single character other than c. Returns the parsed character.

anyChar :: m Char #

This parser succeeds for any character. Returns the parsed character.

Instances
CharParsing ReadP 
Instance details

Defined in Text.Parser.Char

Chunk t => CharParsing (Parser t) 
Instance details

Defined in Text.Parser.Char

CharParsing m => CharParsing (Unhighlighted m) 
Instance details

Defined in Text.Parser.Token

CharParsing m => CharParsing (Unspaced m) 
Instance details

Defined in Text.Parser.Token

CharParsing m => CharParsing (Unlined m) 
Instance details

Defined in Text.Parser.Token

(CharParsing m, MonadPlus m) => CharParsing (IdentityT m) 
Instance details

Defined in Text.Parser.Char

(CharParsing m, MonadPlus m) => CharParsing (StateT s m) 
Instance details

Defined in Text.Parser.Char

Methods

satisfy :: (Char -> Bool) -> StateT s m Char #

char :: Char -> StateT s m Char #

notChar :: Char -> StateT s m Char #

anyChar :: StateT s m Char #

string :: String -> StateT s m String #

text :: Text -> StateT s m Text #

(CharParsing m, MonadPlus m) => CharParsing (StateT s m) 
Instance details

Defined in Text.Parser.Char

Methods

satisfy :: (Char -> Bool) -> StateT s m Char #

char :: Char -> StateT s m Char #

notChar :: Char -> StateT s m Char #

anyChar :: StateT s m Char #

string :: String -> StateT s m String #

text :: Text -> StateT s m Text #

(CharParsing m, MonadPlus m, Monoid w) => CharParsing (WriterT w m) 
Instance details

Defined in Text.Parser.Char

Methods

satisfy :: (Char -> Bool) -> WriterT w m Char #

char :: Char -> WriterT w m Char #

notChar :: Char -> WriterT w m Char #

anyChar :: WriterT w m Char #

string :: String -> WriterT w m String #

text :: Text -> WriterT w m Text #

(CharParsing m, MonadPlus m, Monoid w) => CharParsing (WriterT w m) 
Instance details

Defined in Text.Parser.Char

Methods

satisfy :: (Char -> Bool) -> WriterT w m Char #

char :: Char -> WriterT w m Char #

notChar :: Char -> WriterT w m Char #

anyChar :: WriterT w m Char #

string :: String -> WriterT w m String #

text :: Text -> WriterT w m Text #

(Show s, TextualMonoid s) => CharParsing (Parser g s) Source # 
Instance details

Defined in Text.Grampa.ContextFree.Parallel

Methods

satisfy :: (Char -> Bool) -> Parser g s Char #

char :: Char -> Parser g s Char #

notChar :: Char -> Parser g s Char #

anyChar :: Parser g s Char #

string :: String -> Parser g s String #

text :: Text -> Parser g s Text #

(Show s, TextualMonoid s) => CharParsing (Parser g s) Source # 
Instance details

Defined in Text.Grampa.ContextFree.Continued

Methods

satisfy :: (Char -> Bool) -> Parser g s Char #

char :: Char -> Parser g s Char #

notChar :: Char -> Parser g s Char #

anyChar :: Parser g s Char #

string :: String -> Parser g s String #

text :: Text -> Parser g s Text #

(Show s, TextualMonoid s) => CharParsing (Parser g s) Source # 
Instance details

Defined in Text.Grampa.PEG.Backtrack

Methods

satisfy :: (Char -> Bool) -> Parser g s Char #

char :: Char -> Parser g s Char #

notChar :: Char -> Parser g s Char #

anyChar :: Parser g s Char #

string :: String -> Parser g s String #

text :: Text -> Parser g s Text #

(Show s, TextualMonoid s) => CharParsing (Parser g s) Source # 
Instance details

Defined in Text.Grampa.ContextFree.SortedMemoizing

Methods

satisfy :: (Char -> Bool) -> Parser g s Char #

char :: Char -> Parser g s Char #

notChar :: Char -> Parser g s Char #

anyChar :: Parser g s Char #

string :: String -> Parser g s String #

text :: Text -> Parser g s Text #

(Show s, TextualMonoid s) => CharParsing (Parser g s) Source # 
Instance details

Defined in Text.Grampa.ContextFree.Memoizing

Methods

satisfy :: (Char -> Bool) -> Parser g s Char #

char :: Char -> Parser g s Char #

notChar :: Char -> Parser g s Char #

anyChar :: Parser g s Char #

string :: String -> Parser g s String #

text :: Text -> Parser g s Text #

(Show s, TextualMonoid s) => CharParsing (Parser g s) Source # 
Instance details

Defined in Text.Grampa.PEG.Packrat

Methods

satisfy :: (Char -> Bool) -> Parser g s Char #

char :: Char -> Parser g s Char #

notChar :: Char -> Parser g s Char #

anyChar :: Parser g s Char #

string :: String -> Parser g s String #

text :: Text -> Parser g s Text #

(CharParsing m, MonadPlus m) => CharParsing (ReaderT e m) 
Instance details

Defined in Text.Parser.Char

Methods

satisfy :: (Char -> Bool) -> ReaderT e m Char #

char :: Char -> ReaderT e m Char #

notChar :: Char -> ReaderT e m Char #

anyChar :: ReaderT e m Char #

string :: String -> ReaderT e m String #

text :: Text -> ReaderT e m Text #

Stream s m Char => CharParsing (ParsecT s u m) 
Instance details

Defined in Text.Parser.Char

Methods

satisfy :: (Char -> Bool) -> ParsecT s u m Char #

char :: Char -> ParsecT s u m Char #

notChar :: Char -> ParsecT s u m Char #

anyChar :: ParsecT s u m Char #

string :: String -> ParsecT s u m String #

text :: Text -> ParsecT s u m Text #

(Parsing (p g s), MonoidParsing (Fixed p g), Show s, TextualMonoid s) => CharParsing (Fixed p g s) Source # 
Instance details

Defined in Text.Grampa.ContextFree.LeftRecursive

Methods

satisfy :: (Char -> Bool) -> Fixed p g s Char #

char :: Char -> Fixed p g s Char #

notChar :: Char -> Fixed p g s Char #

anyChar :: Fixed p g s Char #

string :: String -> Fixed p g s String #

text :: Text -> Fixed p g s Text #

(CharParsing m, MonadPlus m, Monoid w) => CharParsing (RWST r w s m) 
Instance details

Defined in Text.Parser.Char

Methods

satisfy :: (Char -> Bool) -> RWST r w s m Char #

char :: Char -> RWST r w s m Char #

notChar :: Char -> RWST r w s m Char #

anyChar :: RWST r w s m Char #

string :: String -> RWST r w s m String #

text :: Text -> RWST r w s m Text #

(CharParsing m, MonadPlus m, Monoid w) => CharParsing (RWST r w s m) 
Instance details

Defined in Text.Parser.Char

Methods

satisfy :: (Char -> Bool) -> RWST r w s m Char #

char :: Char -> RWST r w s m Char #

notChar :: Char -> RWST r w s m Char #

anyChar :: RWST r w s m Char #

string :: String -> RWST r w s m String #

text :: Text -> RWST r w s m Text #

class Alternative m => Parsing (m :: Type -> Type) where #

Additional functionality needed to describe parsers independent of input type.

Minimal complete definition

try, (<?>), notFollowedBy

Methods

(<?>) :: m a -> String -> m a infixr 0 #

Give a parser a name

skipMany :: m a -> m () #

A version of many that discards its input. Specialized because it can often be implemented more cheaply.

skipSome :: m a -> m () #

skipSome p applies the parser p one or more times, skipping its result. (aka skipMany1 in parsec)

unexpected :: String -> m a #

Used to emit an error on an unexpected token

notFollowedBy :: Show a => m a -> m () #

notFollowedBy p only succeeds when parser p fails. This parser does not consume any input. This parser can be used to implement the 'longest match' rule. For example, when recognizing keywords (for example let), we want to make sure that a keyword is not followed by a legal identifier character, in which case the keyword is actually an identifier (for example lets). We can program this behaviour as follows:

 keywordLet  = try $ string "let" <* notFollowedBy alphaNum
Instances
Parsing ReadP 
Instance details

Defined in Text.Parser.Combinators

Methods

try :: ReadP a -> ReadP a #

(<?>) :: ReadP a -> String -> ReadP a #

skipMany :: ReadP a -> ReadP () #

skipSome :: ReadP a -> ReadP () #

unexpected :: String -> ReadP a #

eof :: ReadP () #

notFollowedBy :: Show a => ReadP a -> ReadP () #

Parsing Get 
Instance details

Defined in Text.Parser.Combinators

Methods

try :: Get a -> Get a #

(<?>) :: Get a -> String -> Get a #

skipMany :: Get a -> Get () #

skipSome :: Get a -> Get () #

unexpected :: String -> Get a #

eof :: Get () #

notFollowedBy :: Show a => Get a -> Get () #

Chunk t => Parsing (Parser t) 
Instance details

Defined in Text.Parser.Combinators

Methods

try :: Parser t a -> Parser t a #

(<?>) :: Parser t a -> String -> Parser t a #

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

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

unexpected :: String -> Parser t a #

eof :: Parser t () #

notFollowedBy :: Show a => Parser t a -> Parser t () #

Parsing m => Parsing (Unhighlighted m) 
Instance details

Defined in Text.Parser.Token

Parsing m => Parsing (Unspaced m) 
Instance details

Defined in Text.Parser.Token

Methods

try :: Unspaced m a -> Unspaced m a #

(<?>) :: Unspaced m a -> String -> Unspaced m a #

skipMany :: Unspaced m a -> Unspaced m () #

skipSome :: Unspaced m a -> Unspaced m () #

unexpected :: String -> Unspaced m a #

eof :: Unspaced m () #

notFollowedBy :: Show a => Unspaced m a -> Unspaced m () #

Parsing m => Parsing (Unlined m) 
Instance details

Defined in Text.Parser.Token

Methods

try :: Unlined m a -> Unlined m a #

(<?>) :: Unlined m a -> String -> Unlined m a #

skipMany :: Unlined m a -> Unlined m () #

skipSome :: Unlined m a -> Unlined m () #

unexpected :: String -> Unlined m a #

eof :: Unlined m () #

notFollowedBy :: Show a => Unlined m a -> Unlined m () #

(Parsing m, Monad m) => Parsing (IdentityT m) 
Instance details

Defined in Text.Parser.Combinators

Methods

try :: IdentityT m a -> IdentityT m a #

(<?>) :: IdentityT m a -> String -> IdentityT m a #

skipMany :: IdentityT m a -> IdentityT m () #

skipSome :: IdentityT m a -> IdentityT m () #

unexpected :: String -> IdentityT m a #

eof :: IdentityT m () #

notFollowedBy :: Show a => IdentityT m a -> IdentityT m () #

(Parsing m, MonadPlus m) => Parsing (StateT s m) 
Instance details

Defined in Text.Parser.Combinators

Methods

try :: StateT s m a -> StateT s m a #

(<?>) :: StateT s m a -> String -> StateT s m a #

skipMany :: StateT s m a -> StateT s m () #

skipSome :: StateT s m a -> StateT s m () #

unexpected :: String -> StateT s m a #

eof :: StateT s m () #

notFollowedBy :: Show a => StateT s m a -> StateT s m () #

(Parsing m, MonadPlus m) => Parsing (StateT s m) 
Instance details

Defined in Text.Parser.Combinators

Methods

try :: StateT s m a -> StateT s m a #

(<?>) :: StateT s m a -> String -> StateT s m a #

skipMany :: StateT s m a -> StateT s m () #

skipSome :: StateT s m a -> StateT s m () #

unexpected :: String -> StateT s m a #

eof :: StateT s m () #

notFollowedBy :: Show a => StateT s m a -> StateT s m () #

(Parsing m, MonadPlus m, Monoid w) => Parsing (WriterT w m) 
Instance details

Defined in Text.Parser.Combinators

Methods

try :: WriterT w m a -> WriterT w m a #

(<?>) :: WriterT w m a -> String -> WriterT w m a #

skipMany :: WriterT w m a -> WriterT w m () #

skipSome :: WriterT w m a -> WriterT w m () #

unexpected :: String -> WriterT w m a #

eof :: WriterT w m () #

notFollowedBy :: Show a => WriterT w m a -> WriterT w m () #

(Parsing m, MonadPlus m, Monoid w) => Parsing (WriterT w m) 
Instance details

Defined in Text.Parser.Combinators

Methods

try :: WriterT w m a -> WriterT w m a #

(<?>) :: WriterT w m a -> String -> WriterT w m a #

skipMany :: WriterT w m a -> WriterT w m () #

skipSome :: WriterT w m a -> WriterT w m () #

unexpected :: String -> WriterT w m a #

eof :: WriterT w m () #

notFollowedBy :: Show a => WriterT w m a -> WriterT w m () #

FactorialMonoid s => Parsing (Parser g s) Source # 
Instance details

Defined in Text.Grampa.ContextFree.Parallel

Methods

try :: Parser g s a -> Parser g s a #

(<?>) :: Parser g s a -> String -> Parser g s a #

skipMany :: Parser g s a -> Parser g s () #

skipSome :: Parser g s a -> Parser g s () #

unexpected :: String -> Parser g s a #

eof :: Parser g s () #

notFollowedBy :: Show a => Parser g s a -> Parser g s () #

FactorialMonoid s => Parsing (Parser g s) Source # 
Instance details

Defined in Text.Grampa.ContextFree.Continued

Methods

try :: Parser g s a -> Parser g s a #

(<?>) :: Parser g s a -> String -> Parser g s a #

skipMany :: Parser g s a -> Parser g s () #

skipSome :: Parser g s a -> Parser g s () #

unexpected :: String -> Parser g s a #

eof :: Parser g s () #

notFollowedBy :: Show a => Parser g s a -> Parser g s () #

FactorialMonoid s => Parsing (Parser g s) Source # 
Instance details

Defined in Text.Grampa.PEG.Backtrack

Methods

try :: Parser g s a -> Parser g s a #

(<?>) :: Parser g s a -> String -> Parser g s a #

skipMany :: Parser g s a -> Parser g s () #

skipSome :: Parser g s a -> Parser g s () #

unexpected :: String -> Parser g s a #

eof :: Parser g s () #

notFollowedBy :: Show a => Parser g s a -> Parser g s () #

MonoidNull s => Parsing (Parser g s) Source # 
Instance details

Defined in Text.Grampa.ContextFree.SortedMemoizing

Methods

try :: Parser g s a -> Parser g s a #

(<?>) :: Parser g s a -> String -> Parser g s a #

skipMany :: Parser g s a -> Parser g s () #

skipSome :: Parser g s a -> Parser g s () #

unexpected :: String -> Parser g s a #

eof :: Parser g s () #

notFollowedBy :: Show a => Parser g s a -> Parser g s () #

MonoidNull s => Parsing (Parser g s) Source # 
Instance details

Defined in Text.Grampa.ContextFree.Memoizing

Methods

try :: Parser g s a -> Parser g s a #

(<?>) :: Parser g s a -> String -> Parser g s a #

skipMany :: Parser g s a -> Parser g s () #

skipSome :: Parser g s a -> Parser g s () #

unexpected :: String -> Parser g s a #

eof :: Parser g s () #

notFollowedBy :: Show a => Parser g s a -> Parser g s () #

FactorialMonoid s => Parsing (Parser g s) Source # 
Instance details

Defined in Text.Grampa.PEG.Packrat

Methods

try :: Parser g s a -> Parser g s a #

(<?>) :: Parser g s a -> String -> Parser g s a #

skipMany :: Parser g s a -> Parser g s () #

skipSome :: Parser g s a -> Parser g s () #

unexpected :: String -> Parser g s a #

eof :: Parser g s () #

notFollowedBy :: Show a => Parser g s a -> Parser g s () #

(Parsing m, MonadPlus m) => Parsing (ReaderT e m) 
Instance details

Defined in Text.Parser.Combinators

Methods

try :: ReaderT e m a -> ReaderT e m a #

(<?>) :: ReaderT e m a -> String -> ReaderT e m a #

skipMany :: ReaderT e m a -> ReaderT e m () #

skipSome :: ReaderT e m a -> ReaderT e m () #

unexpected :: String -> ReaderT e m a #

eof :: ReaderT e m () #

notFollowedBy :: Show a => ReaderT e m a -> ReaderT e m () #

(Stream s m t, Show t) => Parsing (ParsecT s u m) 
Instance details

Defined in Text.Parser.Combinators

Methods

try :: ParsecT s u m a -> ParsecT s u m a #

(<?>) :: ParsecT s u m a -> String -> ParsecT s u m a #

skipMany :: ParsecT s u m a -> ParsecT s u m () #

skipSome :: ParsecT s u m a -> ParsecT s u m () #

unexpected :: String -> ParsecT s u m a #

eof :: ParsecT s u m () #

notFollowedBy :: Show a => ParsecT s u m a -> ParsecT s u m () #

(Parsing (p g s), MonoidParsing (Fixed p g)) => Parsing (Fixed p g s) Source # 
Instance details

Defined in Text.Grampa.ContextFree.LeftRecursive

Methods

try :: Fixed p g s a -> Fixed p g s a #

(<?>) :: Fixed p g s a -> String -> Fixed p g s a #

skipMany :: Fixed p g s a -> Fixed p g s () #

skipSome :: Fixed p g s a -> Fixed p g s () #

unexpected :: String -> Fixed p g s a #

eof :: Fixed p g s () #

notFollowedBy :: Show a => Fixed p g s a -> Fixed p g s () #

(Parsing m, MonadPlus m, Monoid w) => Parsing (RWST r w s m) 
Instance details

Defined in Text.Parser.Combinators

Methods

try :: RWST r w s m a -> RWST r w s m a #

(<?>) :: RWST r w s m a -> String -> RWST r w s m a #

skipMany :: RWST r w s m a -> RWST r w s m () #

skipSome :: RWST r w s m a -> RWST r w s m () #

unexpected :: String -> RWST r w s m a #

eof :: RWST r w s m () #

notFollowedBy :: Show a => RWST r w s m a -> RWST r w s m () #

(Parsing m, MonadPlus m, Monoid w) => Parsing (RWST r w s m) 
Instance details

Defined in Text.Parser.Combinators

Methods

try :: RWST r w s m a -> RWST r w s m a #

(<?>) :: RWST r w s m a -> String -> RWST r w s m a #

skipMany :: RWST r w s m a -> RWST r w s m () #

skipSome :: RWST r w s m a -> RWST r w s m () #

unexpected :: String -> RWST r w s m a #

eof :: RWST r w s m () #

notFollowedBy :: Show a => RWST r w s m a -> RWST r w s m () #

class Parsing m => LookAheadParsing (m :: Type -> Type) where #

Additional functionality needed to describe parsers independent of input type.

Methods

lookAhead :: m a -> m a #

lookAhead p parses p without consuming any input.

Instances
LookAheadParsing ReadP 
Instance details

Defined in Text.Parser.LookAhead

Methods

lookAhead :: ReadP a -> ReadP a #

LookAheadParsing Get 
Instance details

Defined in Text.Parser.LookAhead

Methods

lookAhead :: Get a -> Get a #

Chunk i => LookAheadParsing (Parser i) 
Instance details

Defined in Text.Parser.LookAhead

Methods

lookAhead :: Parser i a -> Parser i a #

(LookAheadParsing m, Monad m) => LookAheadParsing (IdentityT m) 
Instance details

Defined in Text.Parser.LookAhead

Methods

lookAhead :: IdentityT m a -> IdentityT m a #

(LookAheadParsing m, MonadPlus m) => LookAheadParsing (StateT s m) 
Instance details

Defined in Text.Parser.LookAhead

Methods

lookAhead :: StateT s m a -> StateT s m a #

(LookAheadParsing m, MonadPlus m) => LookAheadParsing (StateT s m) 
Instance details

Defined in Text.Parser.LookAhead

Methods

lookAhead :: StateT s m a -> StateT s m a #

(LookAheadParsing m, MonadPlus m, Monoid w) => LookAheadParsing (WriterT w m) 
Instance details

Defined in Text.Parser.LookAhead

Methods

lookAhead :: WriterT w m a -> WriterT w m a #

(LookAheadParsing m, MonadPlus m, Monoid w) => LookAheadParsing (WriterT w m) 
Instance details

Defined in Text.Parser.LookAhead

Methods

lookAhead :: WriterT w m a -> WriterT w m a #

FactorialMonoid s => LookAheadParsing (Parser g s) Source # 
Instance details

Defined in Text.Grampa.ContextFree.Parallel

Methods

lookAhead :: Parser g s a -> Parser g s a #

FactorialMonoid s => LookAheadParsing (Parser g s) Source # 
Instance details

Defined in Text.Grampa.ContextFree.Continued

Methods

lookAhead :: Parser g s a -> Parser g s a #

FactorialMonoid s => LookAheadParsing (Parser g s) Source # 
Instance details

Defined in Text.Grampa.PEG.Backtrack

Methods

lookAhead :: Parser g s a -> Parser g s a #

MonoidNull s => LookAheadParsing (Parser g s) Source # 
Instance details

Defined in Text.Grampa.ContextFree.SortedMemoizing

Methods

lookAhead :: Parser g s a -> Parser g s a #

MonoidNull s => LookAheadParsing (Parser g s) Source # 
Instance details

Defined in Text.Grampa.ContextFree.Memoizing

Methods

lookAhead :: Parser g s a -> Parser g s a #

FactorialMonoid s => LookAheadParsing (Parser g s) Source # 
Instance details

Defined in Text.Grampa.PEG.Packrat

Methods

lookAhead :: Parser g s a -> Parser g s a #

(LookAheadParsing m, MonadPlus m) => LookAheadParsing (ReaderT e m) 
Instance details

Defined in Text.Parser.LookAhead

Methods

lookAhead :: ReaderT e m a -> ReaderT e m a #

(Stream s m t, Show t) => LookAheadParsing (ParsecT s u m) 
Instance details

Defined in Text.Parser.LookAhead

Methods

lookAhead :: ParsecT s u m a -> ParsecT s u m a #

(LookAheadParsing (p g s), MonoidParsing (Fixed p g)) => LookAheadParsing (Fixed p g s) Source # 
Instance details

Defined in Text.Grampa.ContextFree.LeftRecursive

Methods

lookAhead :: Fixed p g s a -> Fixed p g s a #

(LookAheadParsing m, MonadPlus m, Monoid w) => LookAheadParsing (RWST r w s m) 
Instance details

Defined in Text.Parser.LookAhead

Methods

lookAhead :: RWST r w s m a -> RWST r w s m a #

(LookAheadParsing m, MonadPlus m, Monoid w) => LookAheadParsing (RWST r w s m) 
Instance details

Defined in Text.Parser.LookAhead

Methods

lookAhead :: RWST r w s m a -> RWST r w s m a #