Safe Haskell | None |
---|---|
Language | Haskell2010 |
First pass of processing a LBNF file.
- Find all the categories defined in a LBNF grammar.
- Complain about duplicate categories, e.g. defined both by rules and
list
ortoken
pragmas. - Drops errorneous definitions, returning a list of errors.
It is possible to continue into pass 2 with the remaining definitions,
should the user desire so (switch
--force
). - Produces a map whose keys are the grammar categories parsed into
ICat
intermediate format and whose values are their first defining occurrences plus kind information.
This pass does not transform the list of parsed definitions into an intermediate format,
e.g. for saving the translations of category names to ICat
.
This could be done, but the translation is cheap and deterministic, so it can be repeated in pass 2.
Synopsis
- data Pass1 = Pass1 {}
- type DefinedICats = Map ICat PCatKind
- data CatKind
- type PCatKind = WithPosition CatKind
- data RuleKind
- stUsedCats :: Lens' Pass1 (Map ICat (List1 (WithPosition Parseable)))
- stKeywords :: Lens' Pass1 (Map Keyword (List1 Position))
- stDefinedCats :: Lens' Pass1 DefinedICats
- checkLBNF :: Grammar -> Check (Grammar, Pass1)
- type M = StateT Pass1 Check
- checkGrammar :: Grammar -> M Grammar
- checkDef :: Def -> M (Maybe Def)
- useCats :: AddCategories a => a -> M ()
- useCatsInternal :: AddCategories a => a -> M ()
- class AddCategories a where
- addCategories :: a -> ReaderT Parseable M ()
- class AddKeywords a where
- addKeywords :: a -> M ()
- ruleKind :: RuleKind -> CatKind
- mergeKind :: CatKind -> CatKind -> Either () CatKind
- parseCat :: Cat -> ICat
- parseCoerceCat :: String -> ICat
- identifierToCat :: Identifier -> Cat
- parseICat :: ICat -> ReaderT DefinedICats Check Cat
- data WithDefinition a = WithDefinition {}
- type PCatOrigin = WithPosition CatOrigin
- data CatOrigin
- type PDCatKind = WithPosition (WithDefinition CatKind)
- data CatInfo = CatInfo {}
- catParsable :: Lens' CatInfo Parseable
- catOrigins :: Lens' CatInfo [PCatOrigin]
Documentation
The state and result of pass1.
Pass1 | |
|
The kind of a category definition.
type PCatKind = WithPosition CatKind Source #
The kind of a rule definition.
stUsedCats :: Lens' Pass1 (Map ICat (List1 (WithPosition Parseable))) Source #
Pass 1 checker
checkGrammar :: Grammar -> M Grammar Source #
Check a whole grammar, swallowing errorneous definitions.
checkDef :: Def -> M (Maybe Def) Source #
Check a definition. Swallow it if it produces a recoverable error.
Collecting categories
useCats :: AddCategories a => a -> M () Source #
useCatsInternal :: AddCategories a => a -> M () Source #
class AddCategories a where Source #
Collect categories used in something.
Instances
AddCategories RHS Source # | |
Defined in BNFC.Check.Pass1 | |
AddCategories Cat Source # | Also adds for each list category its element category, transitively. |
Defined in BNFC.Check.Pass1 | |
AddCategories Item Source # | |
Defined in BNFC.Check.Pass1 | |
AddCategories a => AddCategories [a] Source # | |
Defined in BNFC.Check.Pass1 | |
AddCategories (WithPosition ICat) Source # | Directly add to |
Defined in BNFC.Check.Pass1 addCategories :: WithPosition ICat -> ReaderT Parseable M () Source # |
Collecting keywords
class AddKeywords a where Source #
addKeywords :: a -> M () Source #
Instances
AddKeywords RHS Source # | |
Defined in BNFC.Check.Pass1 addKeywords :: RHS -> M () Source # | |
AddKeywords Item Source # | |
Defined in BNFC.Check.Pass1 addKeywords :: Item -> M () Source # | |
AddKeywords a => AddKeywords [a] Source # | |
Defined in BNFC.Check.Pass1 addKeywords :: [a] -> M () Source # | |
ToPosition p => AddKeywords (p, String) Source # | |
Defined in BNFC.Check.Pass1 addKeywords :: (p, String) -> M () Source # |
Utilities
parseCoerceCat :: String -> ICat Source #
identifierToCat :: Identifier -> Cat Source #
Trash
data WithDefinition a Source #
Instances
type PCatOrigin = WithPosition CatOrigin Source #
ORule | ordinary or |
ORules |
|
OList |
|
OToken |
|
Instances
Eq CatOrigin Source # | |
Ord CatOrigin Source # | |
Defined in BNFC.Check.Pass1 | |
Show CatOrigin Source # | |
type PDCatKind = WithPosition (WithDefinition CatKind) Source #
CatInfo | |
|
catOrigins :: Lens' CatInfo [PCatOrigin] Source #