Safe Haskell | None |
---|---|
Language | Haskell2010 |
Second pass of processing a LBNF file.
Synopsis
- checkLBNF :: Grammar -> Pass1 -> Check LBNF
- filterParseable :: List1 (WithPosition Parseable) -> Maybe (List1 Position)
- type M = ReaderT Pass1 (StateT LBNF Check)
- checkGrammar :: Grammar -> M ()
- checkEntryPoints :: M ()
- checkDef :: Def -> M ()
- parseICat :: ICat -> M Cat
- checkCat :: Cat -> M (WithPosition Cat)
- parseLabel :: Label -> WithPosition Label
- checkItem :: Item -> M (Maybe (WithPosition AItem))
- checkLabel :: WithPosition Label -> FunType -> M ()
- checkListLabelForUniformity :: WithPosition Label -> Cat -> [Cat] -> M ()
- addSig :: LabelName -> WithPosition FunType -> M ()
- checkRHS :: RHS -> M ARHS
- trimRHS :: ARHS -> RHS
- checkRule :: Position -> Parseable -> Label -> Cat -> RHS -> M ()
- addRule :: Position -> RuleOrigin -> Parseable -> Cat -> Label -> ARHS -> M ()
- checkList :: Position -> MinimumSize -> Cat -> Separator' String -> M ()
- checkCoercions :: Position -> Identifier -> Integer -> M ()
- checkRules :: Position -> Identifier -> [RHS] -> M ()
- checkDefine :: Position -> Identifier -> [Arg] -> Exp -> M ()
- addTokenDef :: Position -> Identifier -> PositionToken -> Reg -> M ()
- addLayoutKeyword :: Lens' LBNF LayoutKeywords -> Lens' LBNF LayoutKeywords -> Position -> String -> M ()
- addLineComment :: Position -> String -> M ()
- addBlockComment :: Position -> String -> String -> M ()
Documentation
filterParseable :: List1 (WithPosition Parseable) -> Maybe (List1 Position) Source #
checkGrammar :: Grammar -> M () Source #
checkEntryPoints :: M () Source #
If no entrypoints are given explicitly, take the first non-terminal. If no non-terminal is defined, raise an error
checkCat :: Cat -> M (WithPosition Cat) Source #
Check that a category is defined and convert it into internal representation
parseLabel :: Label -> WithPosition Label Source #
Convert a LBNF label into internal representation.
checkItem :: Item -> M (Maybe (WithPosition AItem)) Source #
Convert an LBNF item (terminal or non-terminal) to internal representation.
checkLabel :: WithPosition Label -> FunType -> M () Source #
Check that (1) ordinary labels define ordinary types (not list types), (2) coercions are have identity type, and (3) list constructors have their respective types.
checkListLabelForUniformity Source #
:: WithPosition Label | Possibly a list label. |
-> Cat | Lhs cat. |
-> [Cat] | Rhs cats. |
-> M () |
Check list rules for uniform indexing.
This flags rules like (:). [Exp] ::= Exp1 [Exp]
.
Such rules make sense in the abstract syntax and the parser,
but may lead to non-faithful printers.
addSig :: LabelName -> WithPosition FunType -> M () Source #
Add label to signature, if it does not exist there yet. Otherwise, throw error.
checkRule :: Position -> Parseable -> Label -> Cat -> RHS -> M () Source #
Check a LBNF rule and convert it into internal form.
addRule :: Position -> RuleOrigin -> Parseable -> Cat -> Label -> ARHS -> M () Source #
Add a well-typed rule to lnbfASTRules
, lbnfASTRulesAP
and, if it is Parseable
, to lbnfParserRules
.
checkList :: Position -> MinimumSize -> Cat -> Separator' String -> M () Source #
Add rules from list pragma.
checkCoercions :: Position -> Identifier -> Integer -> M () Source #
Add rules from coercion
pragma.
E.g. coercions Exp 3
will add the following rules:
_. Exp ::= Exp1; _. Exp1 ::= Exp2; _. Exp2 ::= Exp3; _. Exp3 ::= "(" Exp ")";
checkRules :: Position -> Identifier -> [RHS] -> M () Source #
Add rules from rules
pragma.
checkDefine :: Position -> Identifier -> [Arg] -> Exp -> M () Source #
addTokenDef :: Position -> Identifier -> PositionToken -> Reg -> M () Source #
Add a token category (position carrying or not) defined by a regular expression.
:: Lens' LBNF LayoutKeywords | add here |
-> Lens' LBNF LayoutKeywords | shouldn't be in here |
-> Position | |
-> String | shouldn't be empty |
-> M () |
Add a keyword that starts or stops layout.