| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
CFG
Description
Context-free grammars: syntax and grammar folds.
Synopsis
- data Grammar' x r t = Grammar {
- _grmNumNT :: Int
- _grmNTDict :: Map x NTId
- _grmNTDefs :: IntMap (NTDef' x r t)
- emptyGrammar :: Grammar' x r t
- data NTDef' x r t = NTDef {}
- data Alt' x r t = Alt r (Form' x t)
- newtype Form' x t = Form {}
- data Symbol' x t
- data NT' x = NT {}
- type NTId = Int
- grmNTDefs :: forall x r1 t1 r2 t2 f. Functor f => (IntMap (NTDef' x r1 t1) -> f (IntMap (NTDef' x r2 t2))) -> Grammar' x r1 t1 -> f (Grammar' x r2 t2)
- grmNTDict :: forall x r t f. Functor f => (Map x NTId -> f (Map x NTId)) -> Grammar' x r t -> f (Grammar' x r t)
- grmNumNT :: forall x r t f. Functor f => (Int -> f Int) -> Grammar' x r t -> f (Grammar' x r t)
- ntDef :: forall x r1 t1 r2 t2 f. Functor f => ([Alt' x r1 t1] -> f [Alt' x r2 t2]) -> NTDef' x r1 t1 -> f (NTDef' x r2 t2)
- ntName :: forall x r t f. Functor f => (x -> f x) -> NTDef' x r t -> f (NTDef' x r t)
- data WithNTNames x a = WithNTNames {}
- wntNames :: forall x1 a x2 f. Functor f => (IntMap x1 -> f (IntMap x2)) -> WithNTNames x1 a -> f (WithNTNames x2 a)
- wntThing :: forall x a1 a2 f. Functor f => (a1 -> f a2) -> WithNTNames x a1 -> f (WithNTNames x a2)
- class GetNTNames x a where
- getNTNames :: a -> IntMap x
- data GrmAlg r t a = GrmAlg {}
- gaProduct :: GrmAlg r t a -> [a] -> a
- gaSum :: GrmAlg r t a -> [a] -> a
- class GrmFold r t a b where
- grmIterate :: forall r t a x. (Eq a, Ord a) => GrmAlg r t a -> Grammar' x r t -> a -> Maybe a -> IntMap a
- newtype Guarded = Guarded {
- getGuarded :: Bool
- guardedAlg :: GrmAlg r t Guarded
- computeGuardedness :: Grammar' x r t -> IntMap Guarded
- newtype Nullable = Nullable {
- getNullable :: Bool
- nullableAlg :: GrmAlg r t Nullable
- computeNullable :: Grammar' x r t -> IntMap Nullable
- newtype First t = First {}
- firstAlg :: Ord t => GrmAlg r t (First t)
- emptyFirst :: First t
- concatFirst :: Ord t => First t -> First t -> First t
- type FirstSets t = IntMap (First t)
- computeFirst :: Ord t => Grammar' x r t -> FirstSets t
- firstSet :: Ord t => FirstSets t -> Form' r t -> First t
- data EGrammar' x r t = EGrammar {}
- eFirst :: forall x r t f. Functor f => (FirstSets t -> f (FirstSets t)) -> EGrammar' x r t -> f (EGrammar' x r t)
- eGrm :: forall x r1 t r2 f. Functor f => (Grammar' x r1 t -> f (Grammar' x r2 t)) -> EGrammar' x r1 t -> f (EGrammar' x r2 t)
- eStart :: forall x r t f. Functor f => (NT' x -> f (NT' x)) -> EGrammar' x r t -> f (EGrammar' x r t)
- makeEGrammar :: Ord t => Grammar' x r t -> NT' x -> EGrammar' x r t
Documentation
A grammar over non-terminal names x, rulenames r and an alphabet t consists of definitions of the nonterminals, represented as Ints.
Constructors
| Grammar | |
Fields
| |
Instances
| GetNTNames x (Grammar' x r t) Source # | |
emptyGrammar :: Grammar' x r t Source #
A nonterminal is defined by a list of alternatives.
Each alternative is a rule name plus a sentential form.
Instances
| GrmFold r t a (Alt' x r t) Source # | |
| (Show r, Show t, Show x) => Show (Alt' x r t) Source # | |
| (Eq r, Eq t) => Eq (Alt' x r t) Source # | |
| (Ord r, Ord t) => Ord (Alt' x r t) Source # | |
A sentential form is a string of symbols.
Instances
| GrmFold r t a (Form' r' t) Source # | |
| (Show t, Show x) => Show (Form' x t) Source # | |
| Eq t => Eq (Form' x t) Source # | |
| Ord t => Ord (Form' x t) Source # | |
A symbol is a terminal or a non-terminal.
Instances
| GrmFold r t a (Symbol' r' t) Source # | |
| (DebugPrint x, DebugPrint t) => DebugPrint (Symbol' x t) Source # | |
Defined in ParseTable.Pretty Methods debugPrint :: Symbol' x t -> String Source # | |
| (Show t, Show x) => Show (Symbol' x t) Source # | |
| Eq t => Eq (Symbol' x t) Source # | |
| Ord t => Ord (Symbol' x t) Source # | |
Non-terminals are natural numbers. We store the original name for printing purposes.
grmNTDefs :: forall x r1 t1 r2 t2 f. Functor f => (IntMap (NTDef' x r1 t1) -> f (IntMap (NTDef' x r2 t2))) -> Grammar' x r1 t1 -> f (Grammar' x r2 t2) Source #
grmNTDict :: forall x r t f. Functor f => (Map x NTId -> f (Map x NTId)) -> Grammar' x r t -> f (Grammar' x r t) Source #
grmNumNT :: forall x r t f. Functor f => (Int -> f Int) -> Grammar' x r t -> f (Grammar' x r t) Source #
ntDef :: forall x r1 t1 r2 t2 f. Functor f => ([Alt' x r1 t1] -> f [Alt' x r2 t2]) -> NTDef' x r1 t1 -> f (NTDef' x r2 t2) Source #
Converting NTId back to name.
data WithNTNames x a Source #
Decoration of something with a NT printing dictionary.
Constructors
| WithNTNames | |
Instances
| GetNTNames x (WithNTNames x a) Source # | |
Defined in CFG Methods getNTNames :: WithNTNames x a -> IntMap x Source # | |
| DebugPrint x => DebugPrint (WithNTNames x IGotoActions) Source # | |
Defined in ParseTable.Pretty Methods debugPrint :: WithNTNames x IGotoActions -> String Source # | |
| (Ord r, Ord t, DebugPrint x, DebugPrint r, DebugPrint t) => DebugPrint (WithNTNames x (IPT' x r t)) Source # | |
Defined in ParseTable.Pretty Methods debugPrint :: WithNTNames x (IPT' x r t) -> String Source # | |
wntNames :: forall x1 a x2 f. Functor f => (IntMap x1 -> f (IntMap x2)) -> WithNTNames x1 a -> f (WithNTNames x2 a) Source #
wntThing :: forall x a1 a2 f. Functor f => (a1 -> f a2) -> WithNTNames x a1 -> f (WithNTNames x a2) Source #
class GetNTNames x a where Source #
Methods
getNTNames :: a -> IntMap x Source #
Instances
| GetNTNames x (WithNTNames x a) Source # | |
Defined in CFG Methods getNTNames :: WithNTNames x a -> IntMap x Source # | |
| GetNTNames x (EGrammar' x r t) Source # | |
| GetNTNames x (Grammar' x r t) Source # | |
Generic grammar folds.
A grammar algebra provides an implementation for the operations constituting CFGs.
gaProduct :: GrmAlg r t a -> [a] -> a Source #
n-ary concatenation, with a special case for empty concatenation.
gaSum :: GrmAlg r t a -> [a] -> a Source #
n-ary alternative, with a special case for empty language.
class GrmFold r t a b where Source #
Generic fold over a grammar.
Arguments
| :: forall r t a x. (Eq a, Ord a) | |
| => GrmAlg r t a | Grammar algebra. |
| -> Grammar' x r t | Grammar. |
| -> a | Default/start value. |
| -> Maybe a | Best value (if it exists). |
| -> IntMap a | Final value for each non-terminal. |
Computing properties of non-terminals by saturation.
The iteration is needed to handle the recursion inherent in CFGs.
Requires a bounded lattice a.
Guardedness.
Constructors
| Guarded | |
Fields
| |
guardedAlg :: GrmAlg r t Guarded Source #
Nullability.
Constructors
| Nullable | |
Fields
| |
nullableAlg :: GrmAlg r t Nullable Source #
First sets
firstAlg :: Ord t => GrmAlg r t (First t) Source #
Rules to compute first sets.
FIRST(a) = {a} FIRST(ε) = {ε} FIRST(αβ) = FIRST(α) ∪ (NULLABLE(α) ⇒ FIRST(β)) FIRST(α+β) = FIRST(α) ∪ FIRST(β)
emptyFirst :: First t Source #
Empty FIRST set.
concatFirst :: Ord t => First t -> First t -> First t Source #
FIRST(αβ) = FIRST(α) ∪ (NULLABLE(α) ⇒ FIRST(β)).
computeFirst :: Ord t => Grammar' x r t -> FirstSets t Source #
Compute FIRST sets for all non-terminals.
eFirst :: forall x r t f. Functor f => (FirstSets t -> f (FirstSets t)) -> EGrammar' x r t -> f (EGrammar' x r t) Source #
eGrm :: forall x r1 t r2 f. Functor f => (Grammar' x r1 t -> f (Grammar' x r2 t)) -> EGrammar' x r1 t -> f (EGrammar' x r2 t) Source #