Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Context-free grammars.
Synopsis
- class Cfg cfg t nt where
- nonterminals :: cfg t nt -> Set nt
- terminals :: cfg t nt -> Set t
- productionRules :: cfg t nt -> nt -> Set (Vs t nt)
- startSymbol :: cfg t nt -> nt
- data V t nt
- type Vs t nt = [V t nt]
- isNT :: V t nt -> Bool
- isT :: V t nt -> Bool
- bimapV :: (t -> t') -> (nt -> nt') -> V t nt -> V t' nt'
- bimapVs :: (t -> t') -> (nt -> nt') -> Vs t nt -> Vs t' nt'
- vocabulary :: (Cfg cfg t nt, Ord nt, Ord t) => cfg t nt -> Set (V t nt)
- usedVocabulary :: (Cfg cfg t nt, Ord nt, Ord t) => cfg t nt -> Set (V t nt)
- undeclaredVocabulary :: (Cfg cfg t nt, Ord nt, Ord t) => cfg t nt -> Set (V t nt)
- isFullyDeclared :: (Cfg cfg t nt, Ord nt, Ord t) => cfg t nt -> Bool
- type Production t nt = (nt, Vs t nt)
- productions :: Cfg cfg t nt => cfg t nt -> [Production t nt]
- 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
Class
class Cfg cfg t nt where Source #
Represents a context-free grammar with its nonterminal and terminal types.
:: cfg t nt | |
-> Set nt | the nonterminals of the grammar |
:: cfg t nt | |
-> Set t | the terminals of the grammar |
:: cfg t nt | |
-> nt | the start symbol of the grammar; must be an element of
|
Vocabulary
Vocabulary symbols of the grammar.
Instances
Functor (V t) Source # | |
(Eq t, Eq nt) => Eq (V t nt) Source # | |
(Data t, Data nt) => Data (V t nt) Source # | |
Defined in Data.Cfg.Cfg 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 # | |
(Show t, Show nt) => Show (V t nt) Source # | |
Cfg cfg t nt => CPretty (cfg t nt) (V t nt -> Doc) Source # | |
Defined in Data.Cfg.Cfg |
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 V
s.
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.