Safe Haskell | None |
---|---|
Language | Haskell2010 |
Parsing all context-free grammars using Earley's algorithm.
- data Prod r e t a
- satisfy :: (t -> Bool) -> Prod r e t t
- (<?>) :: Prod r e t a -> e -> Prod r e t a
- data Grammar r e a
- rule :: Prod r e t a -> Grammar r e (Prod r e t a)
- symbol :: Eq t => t -> Prod r e t t
- namedSymbol :: Eq t => t -> Prod r t t t
- word :: Eq t => [t] -> Prod r e t [t]
- data Report e i = Report {
- position :: Int
- expected :: [e]
- unconsumed :: i
- data Result s e i a
- parser :: ListLike i t => (forall r. Grammar r e (Prod r e t a)) -> i -> ST s (Result s e i a)
- allParses :: (forall s. ST s (Result s e i a)) -> ([(a, Int)], Report e i)
- fullParses :: ListLike i t => (forall s. ST s (Result s e i a)) -> ([a], Report e i)
Context-free grammars
A production.
The type parameters are:
a
: The return type of the production.
t
: The type of the terminals that the production operates on.
e
: The type of names, used for example to report expected tokens.
r
: The type of a non-terminal. This plays a role similar to the s
in the
type ST s a
. Since the parser
function expects the r
to be
universally quantified, there is not much to do with this parameter
other than leaving it universally quantified.
As an example,
is the type of a production that
returns an Prod
r String
Char
Int
Int
, operates on (lists of) characters and reports String
names.
Most of the functionality of Prod
s is obtained through its instances, e.g.
Functor
, Applicative
, and Alternative
.
satisfy :: (t -> Bool) -> Prod r e t t Source
Match a token that satisfies the given predicate. Returns the matched token.
(<?>) :: Prod r e t a -> e -> Prod r e t a infixr 0 Source
A named production (used for reporting expected things).
A context-free grammar.
The type parameters are:
a
: The return type of the grammar (often a Prod
).
e
: The type of names, used for example to report expected tokens.
r
: The type of a non-terminal. This plays a role similar to the s
in the
type ST s a
. Since the parser
function expects the r
to be
universally quantified, there is not much to do with this parameter
other than leaving it universally quantified.
Most of the functionality of Grammar
s is obtained through its instances,
e.g. Monad
and MonadFix
. Note that GHC has syntactic sugar for
MonadFix
: use {-# LANGUAGE RecursiveDo #-}
and mdo
instead of
do
.
rule :: Prod r e t a -> Grammar r e (Prod r e t a) Source
Create a new non-terminal by listing its production rule.
Derived operators
namedSymbol :: Eq t => t -> Prod r t t t Source
Match a single token and give it the name of the token.
Parsing
A parsing report, which contains fields that are useful for presenting errors to the user if a parse is deemed a failure. Note however that we get a report even when we successfully parse something.
Report | |
|
The result of a parse.
Ended (Report e i) | The parser ended. |
Parsed a Int i (i -> ST s (Result s e i a)) | The parser parsed something, namely an |
parser :: ListLike i t => (forall r. Grammar r e (Prod r e t a)) -> i -> ST s (Result s e i a) Source
Create a parser from the given grammar.