Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
Context-free grammars.
- data Prod r e t a where
- Terminal :: !(t -> Bool) -> !(Prod r e t (t -> 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
- Plus :: !(Prod r e t a) -> !(Prod r e t a) -> Prod r e t a
- Many :: !(Prod r e t a) -> !(Prod r e t ([a] -> b)) -> Prod r e t b
- Empty :: Prod r e t a
- Named :: !(Prod r e t a) -> e -> 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 where
- rule :: Prod r e t a -> Grammar r e (Prod r e t a)
Documentation
data Prod r e t a where Source
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
.
Terminal :: !(t -> Bool) -> !(Prod r e t (t -> 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 | |
Plus :: !(Prod r e t a) -> !(Prod r e t a) -> Prod r e t a | |
Many :: !(Prod r e t a) -> !(Prod r e t ([a] -> b)) -> Prod r e t b | |
Empty :: Prod r e t a | |
Named :: !(Prod r e t a) -> e -> Prod r e t a |
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).
data Grammar r e a where Source
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
.