Earley-0.13.0.1: 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 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, 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 -> 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 
Instances
Functor (Prod r e t) Source # 
Instance details

Defined in Text.Earley.Grammar

Methods

fmap :: (a -> b) -> Prod r e t a -> Prod r e t b #

(<$) :: a -> Prod r e t b -> Prod r e t a #

Applicative (Prod r e t) Source # 
Instance details

Defined in Text.Earley.Grammar

Methods

pure :: a -> Prod r e t a #

(<*>) :: Prod r e t (a -> b) -> Prod r e t a -> Prod r e t b #

liftA2 :: (a -> b -> c) -> Prod r e t a -> Prod r e t b -> Prod r e t c #

(*>) :: Prod r e t a -> Prod r e t b -> Prod r e t b #

(<*) :: Prod r e t a -> Prod r e t b -> Prod r e t a #

Alternative (Prod r e t) Source # 
Instance details

Defined in Text.Earley.Grammar

Methods

empty :: Prod r e t a #

(<|>) :: Prod r e t a -> Prod r e t a -> Prod r e t a #

some :: Prod r e t a -> Prod r e t [a] #

many :: Prod r e t a -> Prod r e t [a] #

(IsString t, Eq t, a ~ t) => IsString (Prod r e t a) Source #

String literals can be interpreted as Terminals that match that string.

>>> :set -XOverloadedStrings
>>> import Data.Text (Text)
>>> let determiner = "the" <|> "a" <|> "an" :: Prod r e Text Text
Instance details

Defined in Text.Earley.Grammar

Methods

fromString :: String -> Prod r e t a #

Semigroup a => Semigroup (Prod r e t a) Source #

Lifted instance: (<>) = liftA2 (<>)

Instance details

Defined in Text.Earley.Grammar

Methods

(<>) :: Prod r e t a -> Prod r e t a -> Prod r e t a #

sconcat :: NonEmpty (Prod r e t a) -> Prod r e t a #

stimes :: Integral b => b -> Prod r e t a -> Prod r e t a #

Monoid a => Monoid (Prod r e t a) Source #

Lifted instance: mempty = pure mempty

Instance details

Defined in Text.Earley.Grammar

Methods

mempty :: Prod r e t a #

mappend :: Prod r e t a -> Prod r e t a -> Prod r e t a #

mconcat :: [Prod r e t a] -> Prod r e t a #

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 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 b) -> Grammar r b 
FixBind :: (a -> Grammar r a) -> (a -> Grammar r b) -> Grammar r b 
Return :: a -> Grammar r a 
Instances
Monad (Grammar r) Source # 
Instance details

Defined in Text.Earley.Grammar

Methods

(>>=) :: Grammar r a -> (a -> Grammar r b) -> Grammar r b #

(>>) :: Grammar r a -> Grammar r b -> Grammar r b #

return :: a -> Grammar r a #

fail :: String -> Grammar r a #

Functor (Grammar r) Source # 
Instance details

Defined in Text.Earley.Grammar

Methods

fmap :: (a -> b) -> Grammar r a -> Grammar r b #

(<$) :: a -> Grammar r b -> Grammar r a #

MonadFix (Grammar r) Source # 
Instance details

Defined in Text.Earley.Grammar

Methods

mfix :: (a -> Grammar r a) -> Grammar r a #

Applicative (Grammar r) Source # 
Instance details

Defined in Text.Earley.Grammar

Methods

pure :: a -> Grammar r a #

(<*>) :: Grammar r (a -> b) -> Grammar r a -> Grammar r b #

liftA2 :: (a -> b -> c) -> Grammar r a -> Grammar r b -> Grammar r c #

(*>) :: Grammar r a -> Grammar r b -> Grammar r b #

(<*) :: Grammar r a -> Grammar r b -> Grammar r a #

rule :: Prod r e t a -> Grammar r (Prod r e t a) Source #

Create a new non-terminal by giving its production.

runGrammar :: MonadFix m => (forall e t a. Prod r e t a -> m (Prod r e t a)) -> Grammar r b -> m b Source #

Run a grammar, given an action to perform on productions to be turned into non-terminals.