FormalGrammars-0.3.1.2: (Context-free) grammars in formal language theory

Safe HaskellNone
LanguageHaskell2010

FormalLanguage.CFG.Parser

Contents

Description

We define a simple domain-specific language for context-free languages.

TODO we still need to make sure to handle NTs correctly. It should be that we write [X,Y] in multidim cases and then we check in rules if [X,Y] is available ... of course for [X,eps] we then need to check if eps is an epsilon symbol.

Synopsis

Documentation

data GrammarEnv Source #

The environment captures both the current grammar we work with (current) as well as everything we have parsed until now (env).

Constructors

GrammarEnv 

Fields

parseEverything :: Parse m () -> Parse m (Seq Grammar) Source #

Parse everything in the grammar source. The additional argument, normally empty :: Alternative f a, allows for providing additional parsing capabilities -- e.g. for grammar products..

parseGrammar :: Parse m () Source #

The basic parser, which generates a grammar from a description.

setIndices :: Parse m [Index] Source #

Collect all indices and set them as active

parseEmitGrammar :: Parse m () Source #

Which of the intermediate grammar to actually emit as code or text in TeX. Single line: Emit: KnownGrammarName

parseNormStartEps :: Parse m () Source #

Normalize start and epsilon rules in a known Source:, thereby generating a new grammar.

parseOutside :: Parse m () Source #

Try to generate an outside grammar from an inside grammar. The From: name is looked up in the environment.

Outside: NAME
From: (inside)NAME
//

parseCommands :: Parse m () Source #

Some additional commands that change the parsing state.

TODO MonoidOfPairs should generate an adapter function that turns any 2-tape eval function into its k-tape version. This means collecting all name pairs, then emitting the corresponding adapter. We'll also need a monoidal function for combining pairs. (this is along the lines of sum-of-pairs).

Helper parsers

parseSyntacticDecl :: EvalReq -> Parse m SynTermEps Source #

Parses a syntactic (or non-terminal) symbol (for the corresponding index type). Cf. parseSynTermDecl.

parseSynTermDecl :: EvalReq -> Parse m SynTermEps Source #

Parses a syntactic terminal declaration; an inside syntactic variable in an outside context.

parseStartSym :: Parse m Symbol Source #

The syntactic variable here needs to either have no index at all, have a grammar-based index, or have a fully calculated index.

data EvalReq Source #

Constructors

EvalFull

Happens when we actually emit a grammar product (in development)

EvalRule

Happens when we work through the rules

EvalSymb

Happens when we encounter N: and define a symbol

EvalGrammar

Happens when we define grammar-global parameters

parseIndex :: EvalReq -> Stately m [Index] Source #

Parses indices { ... } within curly brackets (braces).

When parsing the EvalSymb case, indexed symbols are being created.

Parsing in rules is handled via EvalRule and actually requires us saying which explicit index we use.

knownSymbol :: EvalReq -> Stately m Symbol Source #

Parses an already known symbol, either syntactic or terminal.

TODO Correctly parse inside-syntactics in outside grammars? Do we want this explicitly?

updateSplitCounts :: [Symbol] -> [Symbol] Source #

For split syntactic variables used in split manner (i.e. @S -> X Y X Y)

TODO error control!

expandIndexed :: Rule -> Parse m [Rule] Source #

Once we have parsed a rule, we still need to extract all active indices in the rule, and enumerate over them. This will finally generate the set of rules we are interested in.

newtype GrammarParser m a Source #

Constructors

GrammarParser 

Instances

Monad m => MonadState GrammarEnv (GrammarParser m) Source # 
Monad m => Monad (GrammarParser m) Source # 

Methods

(>>=) :: GrammarParser m a -> (a -> GrammarParser m b) -> GrammarParser m b #

(>>) :: GrammarParser m a -> GrammarParser m b -> GrammarParser m b #

return :: a -> GrammarParser m a #

fail :: String -> GrammarParser m a #

Functor m => Functor (GrammarParser m) Source # 

Methods

fmap :: (a -> b) -> GrammarParser m a -> GrammarParser m b #

(<$) :: a -> GrammarParser m b -> GrammarParser m a #

Monad m => Applicative (GrammarParser m) Source # 

Methods

pure :: a -> GrammarParser m a #

(<*>) :: GrammarParser m (a -> b) -> GrammarParser m a -> GrammarParser m b #

(*>) :: GrammarParser m a -> GrammarParser m b -> GrammarParser m b #

(<*) :: GrammarParser m a -> GrammarParser m b -> GrammarParser m a #

MonadPlus m => Alternative (GrammarParser m) Source # 
MonadPlus m => MonadPlus (GrammarParser m) Source # 
(MonadPlus m, CharParsing m) => TokenParsing (GrammarParser m) Source # 
(MonadPlus m, CharParsing m) => CharParsing (GrammarParser m) Source # 
(MonadPlus m, Parsing m) => Parsing (GrammarParser m) Source # 

data Result a :: * -> * #

The result of parsing. Either we succeeded or something went wrong.

Constructors

Success a 
Failure ErrInfo 

Instances

Functor Result 

Methods

fmap :: (a -> b) -> Result a -> Result b #

(<$) :: a -> Result b -> Result a #

Applicative Result 

Methods

pure :: a -> Result a #

(<*>) :: Result (a -> b) -> Result a -> Result b #

(*>) :: Result a -> Result b -> Result b #

(<*) :: Result a -> Result b -> Result a #

Foldable Result 

Methods

fold :: Monoid m => Result m -> m #

foldMap :: Monoid m => (a -> m) -> Result a -> m #

foldr :: (a -> b -> b) -> b -> Result a -> b #

foldr' :: (a -> b -> b) -> b -> Result a -> b #

foldl :: (b -> a -> b) -> b -> Result a -> b #

foldl' :: (b -> a -> b) -> b -> Result a -> b #

foldr1 :: (a -> a -> a) -> Result a -> a #

foldl1 :: (a -> a -> a) -> Result a -> a #

toList :: Result a -> [a] #

null :: Result a -> Bool #

length :: Result a -> Int #

elem :: Eq a => a -> Result a -> Bool #

maximum :: Ord a => Result a -> a #

minimum :: Ord a => Result a -> a #

sum :: Num a => Result a -> a #

product :: Num a => Result a -> a #

Traversable Result 

Methods

traverse :: Applicative f => (a -> f b) -> Result a -> f (Result b) #

sequenceA :: Applicative f => Result (f a) -> f (Result a) #

mapM :: Monad m => (a -> m b) -> Result a -> m (Result b) #

sequence :: Monad m => Result (m a) -> m (Result a) #

Alternative Result 

Methods

empty :: Result a #

(<|>) :: Result a -> Result a -> Result a #

some :: Result a -> Result [a] #

many :: Result a -> Result [a] #

Show a => Show (Result a) 

Methods

showsPrec :: Int -> Result a -> ShowS #

show :: Result a -> String #

showList :: [Result a] -> ShowS #

Show a => Pretty (Result a) 

Methods

pretty :: Result a -> Doc #

prettyList :: [Result a] -> Doc #

AsResult (Result a) (Result b) a b 

Methods

_Result :: Prism (Result a) (Result b) (Result a) (Result b) #