Safe Haskell | None |
---|---|
Language | Haskell2010 |
Parser combinators with support for left recursion, following Johnson's "Memoization in Top-Down Parsing".
This implementation is based on an implementation due to Atkey (attached to an edlambda-members mailing list message from 2011-02-15 titled 'Slides for "Introduction to Parser Combinators"').
Note that non-memoised left recursion is not guaranteed to work.
The code contains an important deviation from Johnson's paper: the
check for subsumed results is not included. This means that one can
get the same result multiple times when parsing using ambiguous
grammars. As an example, parsing the empty string using S ∷= ε |
ε
succeeds twice. This change also means that parsing fails to
terminate for some cyclic grammars that would otherwise be handled
successfully, such as S ∷= S | ε
. However, the library is not
intended to handle infinitely ambiguous grammars. (It is unclear to
the author of this module whether the change leads to more
non-termination for grammars that are not cyclic.)
Synopsis
- class (Functor p, Applicative p, Alternative p, Monad p) => ParserClass (p :: Type -> Type) k r tok | p -> k, p -> r, p -> tok where
- sat :: ParserClass p k r tok => (tok -> Bool) -> p tok
- token :: ParserClass p k r tok => p tok
- tok :: (ParserClass p k r tok, Eq tok, Show tok) => tok -> p tok
- doc :: ParserClass p k r tok => Doc -> p a -> p a
- type DocP = (Doc, Int)
- bindP :: Int
- choiceP :: Int
- seqP :: Int
- starP :: Int
- atomP :: Int
- data Parser k r tok a
- data ParserWithGrammar k r tok a
Documentation
class (Functor p, Applicative p, Alternative p, Monad p) => ParserClass (p :: Type -> Type) k r tok | p -> k, p -> r, p -> tok where Source #
parse :: p a -> [tok] -> [a] Source #
Runs the parser.
grammar :: Show k => p a -> Doc Source #
Tries to print the parser, or returns empty
, depending on
the implementation. This function might not terminate.
sat' :: (tok -> Maybe a) -> p a Source #
Parses a token satisfying the given predicate. The computed value is returned.
annotate :: (DocP -> DocP) -> p a -> p a Source #
Uses the given function to modify the printed representation (if any) of the given parser.
memoise :: k -> p r -> p r Source #
Memoises the given parser.
Every memoised parser must be annotated with a unique key. (Parametrised parsers must use distinct keys for distinct inputs.)
memoiseIfPrinting :: k -> p r -> p r Source #
Memoises the given parser, but only if printing, not if parsing.
Every memoised parser must be annotated with a unique key. (Parametrised parsers must use distinct keys for distinct inputs.)
Instances
sat :: ParserClass p k r tok => (tok -> Bool) -> p tok Source #
Parses a token satisfying the given predicate.
token :: ParserClass p k r tok => p tok Source #
Parses a single token.
tok :: (ParserClass p k r tok, Eq tok, Show tok) => tok -> p tok Source #
Parses a given token.
doc :: ParserClass p k r tok => Doc -> p a -> p a Source #
Uses the given document as the printed representation of the
given parser. The document's precedence is taken to be atomP
.
data Parser k r tok a Source #
The parser type.
The parameters of the type Parser k r tok a
have the following
meanings:
k
- Type used for memoisation keys.
r
- The type of memoised values. (Yes, all memoised values have to have the same type.)
tok
- The token type.
a
- The result type.
Instances
Alternative (Parser k r tok) Source # | |
Applicative (Parser k r tok) Source # | |
Defined in Agda.Utils.Parser.MemoisedCPS | |
Functor (Parser k r tok) Source # | |
Monad (Parser k r tok) Source # | |
ParserClass (Parser k r tok) k r tok Source # | |
Defined in Agda.Utils.Parser.MemoisedCPS parse :: Parser k r tok a -> [tok] -> [a] Source # grammar :: Show k => Parser k r tok a -> Doc Source # sat' :: (tok -> Maybe a) -> Parser k r tok a Source # annotate :: (DocP -> DocP) -> Parser k r tok a -> Parser k r tok a Source # memoise :: k -> Parser k r tok r -> Parser k r tok r Source # memoiseIfPrinting :: k -> Parser k r tok r -> Parser k r tok r Source # |
data ParserWithGrammar k r tok a Source #
An extended parser type, with some support for printing parsers.