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

Data.Cfg.Bnf

Description

A simple, concrete instance of Cfg that can be parsed from source.

The grammar of Bnf source is:

grammar ::= (production)+.
production ::= LOWER_CASE_STRING "::=" right_hand_sides ".".
right_hand_sides ::= right_hand_side ("|" right_hand_side)*.
right_hand_side ::= term*.
term ::= UPPER_CASE_STRING | LOWER_CASE_STRING.

where * means zero or more repetitions and + means one or more repetitions. Terminals are indicated by strings of upper-case characters and underscores; nonterminals by strings of lower-case characters and underscores. Quoted strings are literal tokens.

Synopsis

Documentation

newtype Grammar t nt Source #

A simple, concrete instance of Cfg. The terminal and nonterminal symbols of a Grammar are defined to be exactly those appearing the productions. The start symbol is defined to be the head of the first of the productions.

Constructors

Grammar 

Fields

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 #

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

Defined in Data.Cfg.Bnf.Syntax

Methods

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

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

toConstr :: Grammar t nt -> Constr #

dataTypeOf :: Grammar t nt -> DataType #

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

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

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

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

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

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

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

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

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

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

bnf :: QuasiQuoter Source #

QuasiQuoter for BNF source. Generates a value of type Grammar. Not usable in pattern, type or declaration positions.

parse :: String -> Grammar String String Source #

Parses Bnf source into a Grammar.