grammatical-parsers-0.3.2: parsers that combine into grammars

Safe HaskellNone
LanguageHaskell2010

Text.Grampa.ContextFree.Continued

Description

Continuation-passing parser for context-free grammars

Synopsis

Documentation

newtype Parser (g :: (* -> *) -> *) s r Source #

Parser type for context-free grammars that uses a continuation-passing algorithm, fast for grammars in LL(1) class but with potentially exponential performance for longer ambiguous prefixes.

Constructors

Parser 

Fields

Instances
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

MonoidParsing (Parser g) Source # 
Instance details

Defined in Text.Grampa.ContextFree.Continued

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 #

Monad (Parser g s) Source # 
Instance details

Defined in Text.Grampa.ContextFree.Continued

Methods

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

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

return :: a -> Parser g s a #

fail :: String -> Parser g s a #

Functor (Parser g s) Source # 
Instance details

Defined in Text.Grampa.ContextFree.Continued

Methods

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

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

Applicative (Parser g s) Source # 
Instance details

Defined in Text.Grampa.ContextFree.Continued

Methods

pure :: a -> Parser g s a #

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

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

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

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

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

Defined in Text.Grampa.ContextFree.Continued

Methods

empty :: Parser g s a #

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

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

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

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

Defined in Text.Grampa.ContextFree.Continued

Methods

mzero :: Parser g s a #

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

(Lexical g, LexicalConstraint Parser g s, Show s, TextualMonoid s) => TokenParsing (Parser g s) Source # 
Instance details

Defined in Text.Grampa.ContextFree.Continued

Methods

someSpace :: Parser g s () #

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

semi :: Parser g s Char #

highlight :: Highlight -> Parser g s a -> Parser g s a #

token :: 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 #

(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 #

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 () #

Semigroup x => Semigroup (Parser g s x) Source # 
Instance details

Defined in Text.Grampa.ContextFree.Continued

Methods

(<>) :: Parser g s x -> Parser g s x -> Parser g s x #

sconcat :: NonEmpty (Parser g s x) -> Parser g s x #

stimes :: Integral b => b -> Parser g s x -> Parser g s x #

Monoid x => Monoid (Parser g s x) Source # 
Instance details

Defined in Text.Grampa.ContextFree.Continued

Methods

mempty :: Parser g s x #

mappend :: Parser g s x -> Parser g s x -> Parser g s x #

mconcat :: [Parser g s x] -> Parser g s x #

type ResultFunctor Parser Source # 
Instance details

Defined in Text.Grampa.ContextFree.Continued

type GrammarConstraint Parser g Source # 
Instance details

Defined in Text.Grampa.ContextFree.Continued

data Result (g :: (* -> *) -> *) s v Source #

Constructors

Parsed 

Fields

NoParse FailureInfo 
Instances
Functor (Result g s) Source # 
Instance details

Defined in Text.Grampa.ContextFree.Continued

Methods

fmap :: (a -> b) -> Result g s a -> Result g s b #

(<$) :: a -> Result g s b -> Result g s a #

Show1 (Result g s) Source # 
Instance details

Defined in Text.Grampa.ContextFree.Continued

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Result g s a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Result g s a] -> ShowS #

alt :: forall g s a. Parser g s a -> Parser g s a -> Parser g s a Source #

A named and unconstrained version of the <|> operator