Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
Context-free grammars.
- data Prod r e t a where
- Terminal :: !(t -> Maybe a) -> !(Prod r e t (a -> b)) -> Prod r e t b
- NonTerminal :: !(r e t a) -> !(Prod r e t (a -> b)) -> Prod r e t b
- Pure :: a -> Prod r e t a
- Alts :: ![Prod r e t a] -> !(Prod r e t (a -> b)) -> Prod r e t b
- Many :: !(Prod r e t a) -> !(Prod r e t ([a] -> b)) -> Prod r e t b
- Named :: !(Prod r e t a) -> e -> Prod r e t a
- terminal :: (t -> Maybe a) -> Prod r e t a
- (<?>) :: Prod r e t a -> e -> Prod r e t a
- alts :: [Prod r e t a] -> Prod r e t (a -> b) -> Prod r e t b
- data Grammar r a where
- rule :: Prod r e t a -> Grammar r (Prod r e t a)
- runGrammar :: MonadFix m => (forall e t a. Prod r e t a -> m (Prod r e t a)) -> Grammar r b -> m b
Documentation
data Prod r e t a where Source #
A production.
The type parameters are:
a
: The return type of the production.
t
for terminal: The type of the terminals that the production operates
on.
e
for expected: The type of names, used for example to report expected
tokens.
r
for rule: 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
.
Terminal :: !(t -> Maybe a) -> !(Prod r e t (a -> b)) -> Prod r e t b | |
NonTerminal :: !(r e t a) -> !(Prod r e t (a -> b)) -> Prod r e t b | |
Pure :: a -> Prod r e t a | |
Alts :: ![Prod r e t a] -> !(Prod r e t (a -> b)) -> Prod r e t b | |
Many :: !(Prod r e t a) -> !(Prod r e t ([a] -> b)) -> Prod r e t b | |
Named :: !(Prod r e t a) -> e -> Prod r e t a |
Functor (Prod r e t) Source # | |
Applicative (Prod r e t) Source # | |
Alternative (Prod r e t) Source # | |
(IsString t, Eq t, (~) * a t) => IsString (Prod r e t a) Source # | String literals can be interpreted as
|
Semigroup (Prod r e t a) Source # | |
Monoid (Prod r e t a) Source # | |
terminal :: (t -> Maybe a) -> Prod r e t a Source #
Match a token for which the given predicate returns Just a
,
and return the a
.
(<?>) :: Prod r e t a -> e -> Prod r e t a infixr 0 Source #
A named production (used for reporting expected things).
alts :: [Prod r e t a] -> Prod r e t (a -> b) -> Prod r e t b Source #
Smart constructor for alternatives.
data Grammar r a where Source #
A context-free grammar.
The type parameters are:
a
: The return type of the grammar (often a Prod
).
r
for rule: 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
.