Safe Haskell | None |
---|---|
Language | Haskell2010 |
Collection of parsing algorithms with a common interface, operating on grammars represented as records with rank-2 field types.
- class MultiParsing m where
- type ResultFunctor m :: * -> *
- type GrammarConstraint m (g :: (* -> *) -> *) :: Constraint
- simply :: (Only r (p (Only r) s) -> s -> Only r f) -> p (Only r) s r -> s -> f r
- type Grammar g p s = g (p g s)
- type GrammarBuilder g g' p s = g (p g' s) -> g (p g' s)
- type ParseResults = Either ParseFailure
- data ParseFailure = ParseFailure Int [String]
- class MultiParsing m => GrammarParsing m where
- class MonoidParsing m where
- module Text.Parser.Char
- module Text.Parser.Combinators
- module Text.Parser.LookAhead
Parsing methods
class MultiParsing m where Source #
Choose one of the instances of this class to parse with.
type ResultFunctor m :: * -> * Source #
Some parser types produce a single result, others a list of results.
type GrammarConstraint m (g :: (* -> *) -> *) :: Constraint Source #
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.
MultiParsing Parser Source # | Continuation-passing context-free parser
|
MultiParsing Parser Source # | Parallel parser produces a list of all possible parses.
|
MultiParsing Parser Source # | Backtracking PEG parser
|
MultiParsing Parser Source # | Memoizing parser guarantees O(n²) performance for grammars with unambiguous productions, but provides no left recursion support.
|
MultiParsing Parser Source # | Packrat parser
|
MultiParsing (Fixed Parser) Source # | Parser of general context-free grammars, including left recursion.
|
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
type ParseResults = Either ParseFailure Source #
data ParseFailure Source #
A ParseFailure
contains the offset of the parse failure and the list of things expected at that offset.
Parser combinators and primitives
class MultiParsing m => GrammarParsing m where Source #
Parsers that belong to this class memoize the parse results to avoid exponential performance complexity.
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
.
class MonoidParsing m where Source #
Methods for parsing monoidal inputs
endOfInput, getInput, anyToken, satisfy, satisfyChar, satisfyCharInput, notSatisfy, notSatisfyChar, scan, scanChars, string, takeWhile, takeWhile1, takeCharsWhile, takeCharsWhile1, whiteSpace, concatMany
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.
token :: (Eq s, FactorialMonoid s) => s -> m s s Source #
A parser that accepts a specific 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'.
whiteSpace :: TextualMonoid s => m s () Source #
Consume all whitespace characters.
concatMany :: Monoid a => m s a -> m s a Source #
Zero or more argument occurrences like many
, with concatenated monoidal results.
MonoidParsing (Parser g) Source # | |
MonoidParsing (Parser g) Source # | |
MonoidParsing (Parser g) Source # | |
MonoidParsing (Parser g) Source # | |
MonoidParsing (Parser g) Source # | |
MonoidParsing (Fixed Parser g) Source # | |
module Text.Parser.Char
module Text.Parser.Combinators
module Text.Parser.LookAhead