context-free-grammar-0.1.1: Basic algorithms on context-free grammars
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Cfg.Cfg

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

Instances details
(Ord nt, Ord t) => Cfg Grammar t nt Source # 
Instance details

Defined in Data.Cfg.Bnf.Syntax

Methods

nonterminals :: Grammar t nt -> Set nt Source #

terminals :: Grammar t nt -> Set t Source #

productionRules :: Grammar t nt -> nt -> Set (Vs t nt) Source #

startSymbol :: Grammar t nt -> nt Source #

Cfg FreeCfg t nt Source # 
Instance details

Defined in Data.Cfg.FreeCfg

Methods

nonterminals :: FreeCfg t nt -> Set nt Source #

terminals :: FreeCfg t nt -> Set t Source #

productionRules :: FreeCfg t nt -> nt -> Set (Vs t nt) Source #

startSymbol :: FreeCfg t nt -> nt Source #

Vocabulary

data V t nt Source #

Vocabulary symbols of the grammar.

Constructors

T t

a terminal

NT nt

a nonterminal

Instances

Instances details
Functor (V t) Source # 
Instance details

Defined in Data.Cfg.Cfg

Methods

fmap :: (a -> b) -> V t a -> V t b #

(<$) :: a -> V t b -> V t a #

(Eq t, Eq nt) => Eq (V t nt) Source # 
Instance details

Defined in Data.Cfg.Cfg

Methods

(==) :: V t nt -> V t nt -> Bool #

(/=) :: V t nt -> V t nt -> Bool #

(Data t, Data nt) => Data (V t nt) Source # 
Instance details

Defined in Data.Cfg.Cfg

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> V t nt -> c (V t nt) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (V t nt) #

toConstr :: V t nt -> Constr #

dataTypeOf :: V t nt -> DataType #

dataCast1 :: Typeable t0 => (forall d. Data d => c (t0 d)) -> Maybe (c (V t nt)) #

dataCast2 :: Typeable t0 => (forall d e. (Data d, Data e) => c (t0 d e)) -> Maybe (c (V t nt)) #

gmapT :: (forall b. Data b => b -> b) -> V t nt -> V t nt #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> V t nt -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> V t nt -> r #

gmapQ :: (forall d. Data d => d -> u) -> V t nt -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> V t nt -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> V t nt -> m (V t nt) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> V t nt -> m (V t nt) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> V t nt -> m (V t nt) #

(Ord t, Ord nt) => Ord (V t nt) Source # 
Instance details

Defined in Data.Cfg.Cfg

Methods

compare :: V t nt -> V t nt -> Ordering #

(<) :: V t nt -> V t nt -> Bool #

(<=) :: V t nt -> V t nt -> Bool #

(>) :: V t nt -> V t nt -> Bool #

(>=) :: V t nt -> V t nt -> Bool #

max :: V t nt -> V t nt -> V t nt #

min :: V t nt -> V t nt -> V t nt #

(Show t, Show nt) => Show (V t nt) Source # 
Instance details

Defined in Data.Cfg.Cfg

Methods

showsPrec :: Int -> V t nt -> ShowS #

show :: V t nt -> String #

showList :: [V t nt] -> ShowS #

Cfg cfg t nt => CPretty (cfg t nt) (V t nt -> Doc) Source # 
Instance details

Defined in Data.Cfg.Cfg

Methods

cpretty :: MonadReader (V t nt -> Doc) m => cfg t nt -> m Doc Source #

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.