LR-demo
Safe HaskellNone
LanguageHaskell2010

CFG

Description

Context-free grammars: syntax and grammar folds.

Synopsis

Documentation

data Grammar' x r t Source #

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

Instances details
GetNTNames x (Grammar' x r t) Source # 
Instance details

Defined in CFG

Methods

getNTNames :: Grammar' x r t -> IntMap x Source #

data NTDef' x r t Source #

A nonterminal is defined by a list of alternatives.

Constructors

NTDef 

Fields

Instances

Instances details
GrmFold r t a (NTDef' x r t) Source # 
Instance details

Defined in CFG

Methods

grmFold :: GrmAlg r t a -> (NTId -> a) -> NTDef' x r t -> a Source #

(Show x, Eq x) => Semigroup (NTDef' x r t) Source #

Disregarding NTName, we can join non-terminal definitions.

Instance details

Defined in CFG

Methods

(<>) :: NTDef' x r t -> NTDef' x r t -> NTDef' x r t #

sconcat :: NonEmpty (NTDef' x r t) -> NTDef' x r t #

stimes :: Integral b => b -> NTDef' x r t -> NTDef' x r t #

data Alt' x r t Source #

Each alternative is a rule name plus a sentential form.

Constructors

Alt r (Form' x t) 

Instances

Instances details
GrmFold r t a (Alt' x r t) Source # 
Instance details

Defined in CFG

Methods

grmFold :: GrmAlg r t a -> (NTId -> a) -> Alt' x r t -> a Source #

(Show r, Show t, Show x) => Show (Alt' x r t) Source # 
Instance details

Defined in CFG

Methods

showsPrec :: Int -> Alt' x r t -> ShowS #

show :: Alt' x r t -> String #

showList :: [Alt' x r t] -> ShowS #

(Eq r, Eq t) => Eq (Alt' x r t) Source # 
Instance details

Defined in CFG

Methods

(==) :: Alt' x r t -> Alt' x r t -> Bool #

(/=) :: Alt' x r t -> Alt' x r t -> Bool #

(Ord r, Ord t) => Ord (Alt' x r t) Source # 
Instance details

Defined in CFG

Methods

compare :: Alt' x r t -> Alt' x r t -> Ordering #

(<) :: Alt' x r t -> Alt' x r t -> Bool #

(<=) :: Alt' x r t -> Alt' x r t -> Bool #

(>) :: Alt' x r t -> Alt' x r t -> Bool #

(>=) :: Alt' x r t -> Alt' x r t -> Bool #

max :: Alt' x r t -> Alt' x r t -> Alt' x r t #

min :: Alt' x r t -> Alt' x r t -> Alt' x r t #

newtype Form' x t Source #

A sentential form is a string of symbols.

Constructors

Form 

Fields

Instances

Instances details
GrmFold r t a (Form' r' t) Source # 
Instance details

Defined in CFG

Methods

grmFold :: GrmAlg r t a -> (NTId -> a) -> Form' r' t -> a Source #

(Show t, Show x) => Show (Form' x t) Source # 
Instance details

Defined in CFG

Methods

showsPrec :: Int -> Form' x t -> ShowS #

show :: Form' x t -> String #

showList :: [Form' x t] -> ShowS #

Eq t => Eq (Form' x t) Source # 
Instance details

Defined in CFG

Methods

(==) :: Form' x t -> Form' x t -> Bool #

(/=) :: Form' x t -> Form' x t -> Bool #

Ord t => Ord (Form' x t) Source # 
Instance details

Defined in CFG

Methods

compare :: Form' x t -> Form' x t -> Ordering #

(<) :: Form' x t -> Form' x t -> Bool #

(<=) :: Form' x t -> Form' x t -> Bool #

(>) :: Form' x t -> Form' x t -> Bool #

(>=) :: Form' x t -> Form' x t -> Bool #

max :: Form' x t -> Form' x t -> Form' x t #

min :: Form' x t -> Form' x t -> Form' x t #

data Symbol' x t Source #

A symbol is a terminal or a non-terminal.

Constructors

Term t 
NonTerm (NT' x) 

Instances

Instances details
GrmFold r t a (Symbol' r' t) Source # 
Instance details

Defined in CFG

Methods

grmFold :: GrmAlg r t a -> (NTId -> a) -> Symbol' r' t -> a Source #

(DebugPrint x, DebugPrint t) => DebugPrint (Symbol' x t) Source # 
Instance details

Defined in ParseTable.Pretty

Methods

debugPrint :: Symbol' x t -> String Source #

(Show t, Show x) => Show (Symbol' x t) Source # 
Instance details

Defined in CFG

Methods

showsPrec :: Int -> Symbol' x t -> ShowS #

show :: Symbol' x t -> String #

showList :: [Symbol' x t] -> ShowS #

Eq t => Eq (Symbol' x t) Source # 
Instance details

Defined in CFG

Methods

(==) :: Symbol' x t -> Symbol' x t -> Bool #

(/=) :: Symbol' x t -> Symbol' x t -> Bool #

Ord t => Ord (Symbol' x t) Source # 
Instance details

Defined in CFG

Methods

compare :: Symbol' x t -> Symbol' x t -> Ordering #

(<) :: Symbol' x t -> Symbol' x t -> Bool #

(<=) :: Symbol' x t -> Symbol' x t -> Bool #

(>) :: Symbol' x t -> Symbol' x t -> Bool #

(>=) :: Symbol' x t -> Symbol' x t -> Bool #

max :: Symbol' x t -> Symbol' x t -> Symbol' x t #

min :: Symbol' x t -> Symbol' x t -> Symbol' x t #

data NT' x Source #

Non-terminals are natural numbers. We store the original name for printing purposes.

Constructors

NT 

Fields

Instances

Instances details
GrmFold r t a (NT' x) Source # 
Instance details

Defined in CFG

Methods

grmFold :: GrmAlg r t a -> (NTId -> a) -> NT' x -> a Source #

DebugPrint x => DebugPrint (NT' x) Source # 
Instance details

Defined in ParseTable.Pretty

Methods

debugPrint :: NT' x -> String Source #

Show x => Show (NT' x) Source # 
Instance details

Defined in CFG

Methods

showsPrec :: Int -> NT' x -> ShowS #

show :: NT' x -> String #

showList :: [NT' x] -> ShowS #

Eq (NT' x) Source # 
Instance details

Defined in CFG

Methods

(==) :: NT' x -> NT' x -> Bool #

(/=) :: NT' x -> NT' x -> Bool #

Ord (NT' x) Source # 
Instance details

Defined in CFG

Methods

compare :: NT' x -> NT' x -> Ordering #

(<) :: NT' x -> NT' x -> Bool #

(<=) :: NT' x -> NT' x -> Bool #

(>) :: NT' x -> NT' x -> Bool #

(>=) :: NT' x -> NT' x -> Bool #

max :: NT' x -> NT' x -> NT' x #

min :: NT' x -> NT' x -> NT' x #

type NTId = Int Source #

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 #

ntName :: forall x r t f. Functor f => (x -> f x) -> NTDef' x r t -> f (NTDef' x r t) Source #

Converting NTId back to name.

data WithNTNames x a Source #

Decoration of something with a NT printing dictionary.

Constructors

WithNTNames 

Fields

Instances

Instances details
GetNTNames x (WithNTNames x a) Source # 
Instance details

Defined in CFG

Methods

getNTNames :: WithNTNames x a -> IntMap x Source #

DebugPrint x => DebugPrint (WithNTNames x IGotoActions) Source # 
Instance details

Defined in ParseTable.Pretty

(Ord r, Ord t, DebugPrint x, DebugPrint r, DebugPrint t) => DebugPrint (WithNTNames x (IPT' x r t)) Source # 
Instance details

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

Instances details
GetNTNames x (WithNTNames x a) Source # 
Instance details

Defined in CFG

Methods

getNTNames :: WithNTNames x a -> IntMap x Source #

GetNTNames x (EGrammar' x r t) Source # 
Instance details

Defined in CFG

Methods

getNTNames :: EGrammar' x r t -> IntMap x Source #

GetNTNames x (Grammar' x r t) Source # 
Instance details

Defined in CFG

Methods

getNTNames :: Grammar' x r t -> IntMap x Source #

Generic grammar folds.

data GrmAlg r t a Source #

A grammar algebra provides an implementation for the operations constituting CFGs.

Constructors

GrmAlg 

Fields

  • gaTerminal :: t -> a

    Single terminal.

  • gaZero :: a

    Empty language.

  • gaPlus :: a -> a -> a

    Language union.

  • gaEps :: a

    Language of the empty word.

  • gaConcat :: a -> a -> a

    Language concatenation.

  • gaLabel :: r -> a -> a

    Labelled language.

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.

Methods

grmFold :: GrmAlg r t a -> (NTId -> a) -> b -> a Source #

Instances

Instances details
GrmFold r t a (NT' x) Source # 
Instance details

Defined in CFG

Methods

grmFold :: GrmAlg r t a -> (NTId -> a) -> NT' x -> a Source #

GrmFold r t a (Form' r' t) Source # 
Instance details

Defined in CFG

Methods

grmFold :: GrmAlg r t a -> (NTId -> a) -> Form' r' t -> a Source #

GrmFold r t a (Symbol' r' t) Source # 
Instance details

Defined in CFG

Methods

grmFold :: GrmAlg r t a -> (NTId -> a) -> Symbol' r' t -> a Source #

GrmFold r t a (Alt' x r t) Source # 
Instance details

Defined in CFG

Methods

grmFold :: GrmAlg r t a -> (NTId -> a) -> Alt' x r t -> a Source #

GrmFold r t a (NTDef' x r t) Source # 
Instance details

Defined in CFG

Methods

grmFold :: GrmAlg r t a -> (NTId -> a) -> NTDef' x r t -> a Source #

grmIterate Source #

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.

newtype Guarded Source #

Constructors

Guarded 

Fields

Instances

Instances details
Bounded Guarded Source # 
Instance details

Defined in CFG

Show Guarded Source # 
Instance details

Defined in CFG

Eq Guarded Source # 
Instance details

Defined in CFG

Methods

(==) :: Guarded -> Guarded -> Bool #

(/=) :: Guarded -> Guarded -> Bool #

Ord Guarded Source # 
Instance details

Defined in CFG

Nullability.

newtype Nullable Source #

Constructors

Nullable 

Fields

Instances

Instances details
Bounded Nullable Source # 
Instance details

Defined in CFG

Show Nullable Source # 
Instance details

Defined in CFG

Eq Nullable Source # 
Instance details

Defined in CFG

Ord Nullable Source # 
Instance details

Defined in CFG

First sets

newtype First t Source #

Constructors

First 

Fields

Instances

Instances details
Show t => Show (First t) Source # 
Instance details

Defined in CFG

Methods

showsPrec :: Int -> First t -> ShowS #

show :: First t -> String #

showList :: [First t] -> ShowS #

Eq t => Eq (First t) Source # 
Instance details

Defined in CFG

Methods

(==) :: First t -> First t -> Bool #

(/=) :: First t -> First t -> Bool #

Ord t => Ord (First t) Source # 
Instance details

Defined in CFG

Methods

compare :: First t -> First t -> Ordering #

(<) :: First t -> First t -> Bool #

(<=) :: First t -> First t -> Bool #

(>) :: First t -> First t -> Bool #

(>=) :: First t -> First t -> Bool #

max :: First t -> First t -> First t #

min :: First t -> First t -> First t #

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(β)).

type FirstSets t = IntMap (First t) Source #

FIRST sets for all non-terminals.

computeFirst :: Ord t => Grammar' x r t -> FirstSets t Source #

Compute FIRST sets for all non-terminals.

firstSet :: Ord t => FirstSets t -> Form' r t -> First t Source #

data EGrammar' x r t Source #

Enriched grammar.

Constructors

EGrammar 

Fields

Instances

Instances details
GetNTNames x (EGrammar' x r t) Source # 
Instance details

Defined in CFG

Methods

getNTNames :: EGrammar' x r t -> IntMap x Source #

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 #

eStart :: forall x r t f. Functor f => (NT' x -> f (NT' x)) -> EGrammar' x r t -> f (EGrammar' x r t) Source #

makeEGrammar :: Ord t => Grammar' x r t -> NT' x -> EGrammar' x r t Source #