Earley-0.6.0: Parsing all context-free grammars using Earley's algorithm.

Safe HaskellSafe
LanguageHaskell2010

Text.Earley.Grammar

Description

Context-free grammars.

Synopsis

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, Prod r String Char Int is the type of a production that returns an Int, operates on (lists of) characters and reports String names.

Most of the functionality of Prods is obtained through its instances, e.g. Functor, Applicative, and Alternative.

Constructors

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 

Instances

Functor (Prod r e t) Source 
Applicative (Prod r e t) Source 
Alternative (Prod r e t) Source 
Monoid (Prod r e t a) Source 

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 Grammars 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.

Constructors

RuleBind :: Prod r e t a -> (Prod r e t a -> Grammar r e b) -> Grammar r e b 
FixBind :: (a -> Grammar r e a) -> (a -> Grammar r e b) -> Grammar r e b 
Return :: a -> Grammar r e a 

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.