context-free-grammar-0.0.1: Basic algorithms on context-free grammars

Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Cfg.Cfg

Contents

Description

Context-free grammars.

Synopsis

Class

class Cfg cfg t nt where Source

Represents a context-free grammar with its nonterminal and terminal types.

Methods

nonterminals Source

Arguments

:: cfg t nt 
-> Set nt

the nonterminals of the grammar

terminals Source

Arguments

:: cfg t nt 
-> Set t

the terminals of the grammar

productionRules Source

Arguments

:: cfg t nt 
-> nt 
-> Set (Vs t nt)

the productions of the grammar

startSymbol Source

Arguments

:: cfg t nt 
-> nt

the start symbol of the grammar; must be an element of nonterminals cfg

Instances

Cfg FreeCfg t nt 
(Ord nt, Ord t) => Cfg Grammar t nt 

Vocabulary

data V t nt Source

Vocabulary symbols of the grammar.

Constructors

T t

a terminal

NT nt

a nonterminal

Instances

Functor (V t) 
(Eq t, Eq nt) => Eq (V t nt) 
(Data t, Data nt) => Data (V t nt) 
(Ord t, Ord nt) => Ord (V t nt) 
(Show t, Show nt) => Show (V t nt) 
Typeable (* -> * -> *) V 
Cfg cfg t nt => CPretty (cfg t nt) (V t nt -> Doc) 

type Vs t nt = [V t nt] Source

Synonym for lists of vocabulary symbols.

isNT :: V t nt -> Bool Source

Returns True iff the vocabularly symbols is a nonterminal.

isT :: V t nt -> Bool Source

Returns True iff the vocabularly symbols is a terminal.

bimapV :: (t -> t') -> (nt -> nt') -> V t nt -> V t' nt' Source

Maps over the terminal and nonterminal symbols in a V.

bimapVs :: (t -> t') -> (nt -> nt') -> Vs t nt -> Vs t' nt' Source

Maps over the terminal and nonterminal symbols in a list of Vs.

vocabulary :: (Cfg cfg t nt, Ord nt, Ord t) => cfg t nt -> Set (V t nt) Source

Returns the vocabulary symbols of the grammar: elements of terminals and nonterminals.

usedVocabulary :: (Cfg cfg t nt, Ord nt, Ord t) => cfg t nt -> Set (V t nt) Source

Returns all vocabulary used in the productions plus the start symbol.

undeclaredVocabulary :: (Cfg cfg t nt, Ord nt, Ord t) => cfg t nt -> Set (V t nt) Source

Returns all vocabulary used in the productions plus the start symbol but not declared in nonterminals or terminals.

isFullyDeclared :: (Cfg cfg t nt, Ord nt, Ord t) => cfg t nt -> Bool Source

Returns True all the vocabulary used in the grammar is declared.

Productions

type Production t nt = (nt, Vs t nt) Source

Productions over vocabulary symbols

productions :: Cfg cfg t nt => cfg t nt -> [Production t nt] Source

Returns the productions of the grammar.

Utility functions

eqCfg :: forall cfg cfg' t nt. (Cfg cfg t nt, Cfg cfg' t nt, Eq nt, Eq t) => cfg t nt -> cfg' t nt -> Bool Source

Returns True iff the two inhabitants of Cfg are equal.