diff --git a/docs/user_guide.rst b/docs/user_guide.rst index 041c508a..c4e1e287 100644 --- a/docs/user_guide.rst +++ b/docs/user_guide.rst @@ -284,3 +284,81 @@ BNFC adds the grammar name as a file extension. So if the grammar file is named ``Calc.cf``, the lexer will be associated to the file extension ``.calc``. To associate other file extensions to a generated lexer, you need to modify (or subclass) the lexer. + +Python Backend +=============== + +The BNF Converter's Python Backend generates a Python frontend, that uses +Lark, to parse input into an AST (abstract syntax tree). + +Lark and Python 3.10 or higher is needed. + +Example usage: :: + + bnfc --python Calc.cf + + +.. list-table:: The result is a set of files: + :widths: 25 25 + :header-rows: 1 + + * - Filename + - Description + * - bnfcPyGenCalc/Absyn.py + - Provides the classes for the abstract syntax. + * - bnfcPyGenCalc/ParserDefs.py + - Provides Lark with the information needed to build the lexer and parser. + * - bnfcPyGenCalc/PrettyPrinter.py + - Provides printing for both the AST and the linearized tree. + * - genTest.py + - A ready test-file, that uses the generated frontend to convert input into an AST. + * - skele.py + - Provides skeleton code to deconstruct an AST, using structural pattern matching. + +Optionally one may with ``-m``` also create a makefile that contains the target +"distclean" to remove the generated files. + +Testing the frontend +.................... + +It's possible to pipe input, like:: + + echo "(1 + 2) * 3" | python3 genTest.py + +or:: + + python3 genTest.py < file.txt + +and it's possible to just use an argument:: + + python3 genTest.py file.txt + + +Caveats +....... + +Several entrypoints: + The testfile genTest.py only uses the first entrypoint used by default. To + use all entrypoints, set the start parameter to "start_". If the + entrypoints cause reduce/reduce conflicts, a lark GrammarError will be + produced. + +Results from the parameterized tests: + While the Python backend generates working frontends for the example + grammars, five "failures" and six "errors" among the regression + tests are reported. + +Skeleton code for using lists as entrypoints: + Matchers for using lists, such as [Exp], are not generated in the + skeleton code as it may confuse users if the grammar uses several different + list categories, as a user may then try to pattern match lists without + checking what type the elements have. Users are instead encouraged to use + non-list entrypoints. + +Using multiple separators + Using multiple separators for the same category, such as below, generates + Python functions with overlapping names, causing runtime errors.:: + + separator Exp1 "," ; + separator Exp1 ";" ; + diff --git a/document/BNF_Converter_Python_Mode.html b/document/BNF_Converter_Python_Mode.html new file mode 100644 index 00000000..4ffb46f6 --- /dev/null +++ b/document/BNF_Converter_Python_Mode.html @@ -0,0 +1,198 @@ + +
+ ++ The BNF Converter's Python Backend generates a Python frontend, that uses + Lark, to parse input into an AST (abstract syntax tree). +
+
+ BNFC on Github:
+ https://github.com/BNFC/bnfc
+
+ Lark github:
+ https://github.com/lark-parser/lark
+
+ Python 3.10 or higher is needed. +
++The result is a set of files: +
+Filename: | Description: | +
---|---|
bnfcGenNAME/Absyn.py | Provides the classes for the abstract syntax. | +
bnfcGenNAME/ParserDefs.py | Provides Lark with the information needed to build the lexer and parser. | +
bnfcGenNAME/PrettyPrinter.py | Provides printing for both the AST and the linearized tree. | +
genTest.py | A ready test-file, that uses the generated frontend to convert input into an AST. | +
skele.py | Provides skeleton code to deconstruct an AST, using structural pattern matching. | +
+ The following example uses a frontend that is generated from a C-like grammar. +
++ $ python3 genTest.py < hello.c +
+
+ Parse Successful!
+
+ [Abstract Syntax]
+ (PDefs [(DFun Type_int "main" [] [(SExp (EApp "printString" [(EString "Hello world")])), (SReturn (EInt 0))])])
+
+ [Linearized Tree]
+ int main ()
+ {
+ printString ("Hello world");
+ return 0;
+ }
+
+ The AST is built up using instances of Python classes, using the dataclass decorator, such as: +
+
+@dataclass
+class EAdd:
+ exp_1: Exp
+ exp_2: Exp
+ _ann_type: _AnnType = field(default_factory=_AnnType)
+
+ The "_ann_type" variable is a placeholder that can be used to store useful information, + for example type-information in order to create a type-annotated AST. +
++ The skeleton file serves as a template, to create an interpreter for example. + Two different types of matchers are generated: the first with all the value + categories together, and a second type where each matcher only has one + individual value category, as in the example below: +
+
+def matcherExp(exp_: Exp):
+ match exp_:
+ case EAdd(exp_1, exp_2, _ann_type):
+ # Exp "+" Exp1
+ raise Exception('EAdd not implemented')
+ case ESub(exp_1, exp_2, _ann_type):
+ ...
+
+ This can be modified, in order to return the addition of each evaluated argument + category, into: +
+
+ def matcherExp(exp_: Exp):
+ match exp_:
+ case EAdd(exp_1, exp_2, _ann_type):
+ # Exp "+" Exp1
+ return matcherExp(exp_1) + matcherExp(exp_2)
+ case ESub(exp_1, exp_2, _ann_type):
+ ...
+
+ The function can now be imported and used in the generated test file + (similarly to how the pretty printer is imported and used): +
+
+ from skele import matcherExp
+ ...
+ print(matcherExp(ast))
+
+ Matchers for using lists, such as [Exp], are not generated in the + skeleton code as it may confuse users if the grammar uses several different + list categories, as a user may then try to pattern match lists without + checking what type the elements have. Users are instead encouraged to use + non-list entrypoints. +
++ The improper way to iterate over lists, as the value category is unknown: +
+
+ case list():
+ for ele in ast:
+ ...
+
+ The proper way to deconstruct lists, where we know the value category: +
+
+ case RuleName(listexp_):
+ for exp in listexp_:
+ ...
+
+ Using multiple separators for the same category, such as below, generates + Python functions with overlapping names, causing runtime errors. +
+
+ separator Exp1 "," ;
+ separator Exp1 ";" ;
+
+ The testfile genTest.py only uses the first entrypoint used by default. To + use all entrypoints, set the start parameter to "start_". If the + entrypoints cause reduce/reduce conflicts, a lark GrammarError will be + produced. +
++ While the Python backend generates working frontends for the example + grammars, five "failures" and six "errors" among the regression + tests are reported. +
+ diff --git a/source/BNFC.cabal b/source/BNFC.cabal index 7300a8d2..9280a8f3 100644 --- a/source/BNFC.cabal +++ b/source/BNFC.cabal @@ -280,6 +280,14 @@ library BNFC.Backend.TreeSitter.CFtoTreeSitter BNFC.Backend.TreeSitter.RegToJSReg + -- Python backend + BNFC.Backend.Python + BNFC.Backend.Python.CFtoPyAbs + BNFC.Backend.Python.CFtoPyPrettyPrinter + BNFC.Backend.Python.RegToFlex + BNFC.Backend.Python.PyHelpers + BNFC.Backend.Python.CFtoPySkele + ----- Testing -------------------------------------------------------------- test-suite unit-tests diff --git a/source/main/Main.hs b/source/main/Main.hs index 754bf268..6377611f 100644 --- a/source/main/Main.hs +++ b/source/main/Main.hs @@ -26,6 +26,7 @@ import BNFC.Backend.Latex import BNFC.Backend.OCaml import BNFC.Backend.Pygments import BNFC.Backend.TreeSitter +import BNFC.Backend.Python import BNFC.CF (CF) import BNFC.GetCF import BNFC.Options hiding (make, Backend) @@ -83,3 +84,5 @@ maketarget = \case TargetPygments -> makePygments TargetCheck -> error "impossible" TargetTreeSitter -> makeTreeSitter + TargetPython -> makePython + \ No newline at end of file diff --git a/source/src/BNFC/Backend/Python.hs b/source/src/BNFC/Backend/Python.hs new file mode 100644 index 00000000..e0dc012d --- /dev/null +++ b/source/src/BNFC/Backend/Python.hs @@ -0,0 +1,137 @@ +{-# LANGUAGE NoImplicitPrelude #-} +{-# LANGUAGE OverloadedStrings #-} + +{- + BNF Converter: Python main file + Copyright (C) 2004 Author: Bjorn Werner +-} + +module BNFC.Backend.Python (makePython) where + +import Prelude hiding ((<>)) +import System.FilePath ((>)) +import BNFC.CF (CF, firstEntry) +import BNFC.Options (SharedOptions, optMake, lang) +import BNFC.Backend.Base (MkFiles, mkfile) +import BNFC.Backend.Python.CFtoPyAbs (cf2PyAbs) +import BNFC.Backend.Python.CFtoPyPrettyPrinter (cf2PyPretty) +import BNFC.Backend.Python.CFtoPySkele (cf2PySkele) +import BNFC.Backend.Python.PyHelpers +import BNFC.PrettyPrint +import Data.Char (toLower, isLetter) +import qualified BNFC.Backend.Common.Makefile as Makefile + + +-- | Entrypoint for BNFC to use the Python backend. +makePython :: SharedOptions -> CF -> MkFiles () +makePython opts cf = do + let pkgName = "bnfcPyGen" ++ filter isLetter name + let (parsingDefs, abstractClasses) = cf2PyAbs pkgName cf + let prettyPrinter = cf2PyPretty pkgName cf + let skeletonCode = cf2PySkele pkgName cf + mkPyFile (pkgName ++ "/ParsingDefs.py") parsingDefs + mkPyFile (pkgName ++ "/Absyn.py") abstractClasses + mkPyFile (pkgName ++ "/PrettyPrinter.py") prettyPrinter + mkPyFile "skele.py" skeletonCode + mkPyFile "genTest.py" (pyTest pkgName cf) + Makefile.mkMakefile (optMake opts) $ makefile pkgName (optMake opts) + where + name :: String + name = lang opts + mkPyFile x = mkfile x comment + + +-- | A makefile with distclean and clean specifically for the testsuite. No +-- "all" is needed as bnfc has already generated the necessary Python files. +makefile :: String -> Maybe String -> String -> Doc +makefile pkgName optMakefileName basename = vcat + [ + Makefile.mkRule "all" [] + [ "@echo \"Doing nothing: No compilation of the parser needed.\"" ] + , Makefile.mkRule "clean" [] + [ "rm -f parser.out parsetab.py" ] + , Makefile.mkRule "distclean" [ "vclean" ] [] + , Makefile.mkRule "vclean" [] + [ "rm -f " ++ unwords + [ + pkgName ++ "/ParsingDefs.py", + pkgName ++ "/Absyn.py", + pkgName ++ "/PrettyPrinter.py", + pkgName ++ "/ParsingDefs.py.bak", + pkgName ++ "/Absyn.py.bak", + pkgName ++ "/PrettyPrinter.py.bak", + "skele.py", + "genTest.py", + "skele.py.bak", + "genTest.py.bak" + ], + "rm -f " ++ pkgName ++ "/__pycache__/*.pyc", + "rm -fd " ++ pkgName ++ "/__pycache__", + "rmdir " ++ pkgName, + "rm -f __pycache__/*.pyc", + "rm -fd __pycache__", + "rm -f " ++ makefileName, + "rm -f " ++ makefileName ++ ".bak" + ] + ] + where + makefileName = case optMakefileName of + Just s -> s + Nothing -> "None" -- No makefile will be created. + + +-- | Put string into a comment. +comment :: String -> String +comment x = "# " ++ x + + +-- Produces the content for the testing file, genTest.py. +pyTest :: String -> CF -> String +pyTest pkgName cf = unlines + [ "import sys" + , "from " ++ pkgName ++ ".ParsingDefs import *" + , "from " ++ pkgName ++ ".PrettyPrinter import printAST, lin, renderC" + , "" + , "# Suggested input options:" + , "# python3 genTest.py < sourcefile" + , "# python3 genTest.py sourcefile inputfile (i.e. for interpreters)." + , "inputFile = None" + , "if len(sys.argv) > 1:" + , " f = open(sys.argv[1], 'r')" + , " inp = f.read()" + , " f.close()" + , " if len(sys.argv) > 2:" + , " inputFile = sys.argv[2]" + , "else:" + , " inp = ''" + , " for line in sys.stdin:" + , " inp += line" + , "" + , "def onError(e):" + , " print(e)" + , " print('Parse failed')" + , " quit(1)" + , "" + , "# Creates the Lark parser with the given grammar. By default to the first" + , "# entrypoint. Other entrypoints exist in ParsingDefs.py." + , "parser = Lark(grammar, start='" ++ defaultEntrypoint ++ "', parser='lalr', lexer='basic', transformer=TreeTransformer())" + , "" + , "# By default the first entrypoint is used. See ParsingDefs.py for alternatives." + , "ast = parser.parse(inp, on_error=onError)" + , "if ast:" + , " print('Parse Successful!\\n')" + , " print('[Abstract Syntax]')" + , " print(printAST(ast))" + , " print('\\n[Linearized Tree]')" + , " linTree = lin(ast)" + , " print(renderC(linTree))" + , " print()" + , "else:" + , " print('Parse failed')" + , " quit(1)" + ] + where + defaultEntrypoint = map toLower + ((translateToList . show . firstEntry) cf) + + diff --git a/source/src/BNFC/Backend/Python/CFtoPyAbs.hs b/source/src/BNFC/Backend/Python/CFtoPyAbs.hs new file mode 100644 index 00000000..dd346984 --- /dev/null +++ b/source/src/BNFC/Backend/Python/CFtoPyAbs.hs @@ -0,0 +1,426 @@ + +{- + BNF Converter: Python abstract syntax and parsing definitions generator + Copyright (C) 2024 Author: Bjorn Werner + Based on CFtoCAbs.hs, Copyright (C) 2004 Michael Pellauer +-} + +module BNFC.Backend.Python.CFtoPyAbs (cf2PyAbs) where +import Data.List ( nub, intercalate ) +import BNFC.CF +import BNFC.Backend.Python.PyHelpers +import BNFC.Backend.Python.RegToFlex (printRegFlex, escapeChar) +import BNFC.Backend.Common.NamedVariables +import Text.PrettyPrint (Doc, render) +import Data.Either (lefts) +import Data.Char (toLower, toUpper, isLower) +import qualified Data.List.NonEmpty as List1 + + +-- | The result is ParsingDefs.py & Absyn.py +cf2PyAbs + :: String + -> CF -- ^ Grammar. + -> (String, String) -- ParsingDefs.py, Absyn.py. +cf2PyAbs pkgName cf = ( unlines + [ "from lark import Lark, Transformer, v_args" + , "from dataclasses import dataclass" + , "from " ++ pkgName ++ ".Absyn import *" + , "" + , createGrammar cf + , createTransformer cf + , createDefineFunctions cf + , "" + ] + , unlines + ["from typing import List as _List" + ,"# Value categories (no coercsions):" + , unlines valueCatsClasses + , "" + , placeholderVariableClass + , "" + ,"# Rules:" + ,"from dataclasses import dataclass, field" + ,"\n" ++ (unlines dataClasses) + ] + ) + where + rules = cfgRules cf + + -- To create Absyn.py + dataClasses :: [String] + dataClasses = map makePythonClass + [ r | r <- rules, not (isDefinedRule r) + , not (isNilCons r) + , not (isCoercion r) + ] + + rulesNoListConstructors = + [r | r <- (cfgRules cf), not (isNilCons r), not (isCoercion r) ] + + -- Note: Custom tokens are set to inherit "str". + valueCatNames = nub $ + (map (unkw . show . normCat . valCat) rulesNoListConstructors) ++ + (map ((++ "(str)") . unkw) (tokenNames cf)) ++ + [ "String(str)" + , "Char(str)" + , "Ident(str)" + , "Integer(int)" + , "Double(float)" + ] + valueCatsClasses = map createValueCatClass valueCatNames + + +-- Creates a grammar for Lark. Not that it is a real string (r"..."). +createGrammar :: CF -> String +createGrammar cf = unlines + [ "grammar = r\"\"\"" + , " ?start_: " ++ entryOrClause + , "" + , unlines orClauses + , larkLiterals cf + , unlines singleComments + , unlines multiComments + , " %import common.WS" + , " %ignore WS" + , "\"\"\"" + ] + where + aCats = reallyAllCats cf + rs = cfgRules cf + + enumeratedRules :: [(Int, Rul RFun)] + enumeratedRules = enumerateAllDefinedRules rs 1 [] + orClauses = map (createOrClause enumeratedRules) aCats + + (multiMatchers, singleMatchers) = comments cf + singleComments = map createLineCommentMatcher singleMatchers + multiComments = map createMultiLineCommentMatcher multiMatchers + + strListEntryPoints = map ((map toLower) . translateToList . show) + ((List1.toList . allEntryPoints) cf) + entryOrClause = intercalate "\n | " strListEntryPoints + + +-- Enumerates all (only defined relevant) rules to prevent naming overlap. +enumerateAllDefinedRules :: [Rul RFun] -> Int -> [(Int, Rul RFun)] + -> [(Int, Rul RFun)] +enumerateAllDefinedRules [] _ irs = irs +enumerateAllDefinedRules (r:rs) n irs + | isDefinedRule r = enumerateAllDefinedRules rs (n+1) (irs ++ [(n, r)]) + | otherwise = enumerateAllDefinedRules rs n (irs ++ [(0, r)]) + + +-- Creates an or clause with all rules for a given category. +createOrClause :: [(Int, Rul RFun)] -> Cat -> String +createOrClause irs c = unlines + [ " ?" ++ map toLower (translateToList (show c)) ++ ": " ++ + intercalate "\n | " + (map createProdAndNameForRule catsIrs) + ] + where + catsIrs = [(n, removeWhiteSpaceSeparators r) | (n, r) <- irs, + valCat r == c, isParsable r] + + +-- Creates an entry for an or clause. +createProdAndNameForRule :: (Int, Rul RFun) -> String +createProdAndNameForRule (n, r) = prodToDocStr (rhsRule r) ++ + if (not (isCoercion r)) then " -> " ++ map toLower name else "" + where + name + | isNilFun r = "nil" ++ (identCat . valCat) r + | isOneFun r = "one" ++ (identCat . valCat) r + | isConsFun r = "cons" ++ (identCat . valCat) r + | isDefinedRule r = "d" ++ show n ++ "_r_" ++ funName r + | otherwise = "r_" ++ map toLower (funName r) ++ toOrd (funName r) + + +-- Creates the literals for a grammar for Lark.Priority is set after the +-- dot, such as "Name.PRIO". For literals with the same priority, it appears +-- that Lark (with basic mode) prioritizes the longest regular +-- expression, not the longest matched literal. +larkLiterals :: CF -> String +larkLiterals cf = unlines $ concat + [ + ifC catString [createLiteral "String.1" "\"(\\\\.|[^\"])*\""] + , ifC catChar [createLiteral "Char.1" "\\'(\\\\x[0-9a-f][0-9a-f]|\\\\?[\\S\\s])\\'"] + , ifC catDouble [createLiteral "Double.1" "\\d+\\.\\d+(e-?\\d+)?"] + , ifC catInteger [createLiteral "Integer.1" "\\d+"] + -- Prolog requires user defined tokens to have priority over Ident; C + -- requires Double to have priority over user defined tokens, as C has + -- "CDouble" matching "3." in 3.14. + , userDefTokens + , ifC catIdent [createLiteral "Ident" "[A-Za-z_]\\w*"] + ] + where + ifC :: TokenCat -> [String] -> [String] + ifC cat s = if isUsedCat cf (TokenCat cat) then s else [] + + userDefTokens :: [String] + userDefTokens = [ + createLiteral name (printRegFlex exp) | (name, exp) <- tokenPragmas cf + ] + + createLiteral :: String -> String -> String + createLiteral name regex = + " " ++ map toUpper name ++ ": /" ++ regex ++ "/" + + +-- Creates the class transformer, where each member method tells Lark how +-- to transform some parsed node in the tree. +createTransformer :: CF -> String +createTransformer cf = unlines + [ "#transformer" + , "class TreeTransformer(Transformer):" + , unlines (map createRuleTransform rs) + , unlines (map makeDefineTransform enumeratedRDs) + , unlines (map createListTransform listRules) + , createTokenTransformers cf + ] + where + enumeratedRules :: [(Int, Rul RFun)] + enumeratedRules = enumerateAllDefinedRules (cfgRules cf) 1 [] + + rs = [r | r <- cfgRules cf + , not (isCoercion r) + , not (isNilCons r) + , not (isDefinedRule r)] + listRules = [r | r <- cfgRules cf, isNilCons r] + + enumeratedRDs = [(n, r, d) | (n, r) <- enumeratedRules, d <- definitions cf + , not (isCoercion r) + , not (isNilCons r) + , isDefinedRule r + , nameCorresponds ((wpThing . defName) d) (funName r)] + + +-- Creates a transform for a rule +createRuleTransform :: Rul RFun -> String +createRuleTransform r = unlines + [ " @v_args(inline=True)" + , " def r_" ++ nameWithUnicode ++ "(self" ++ + concat (map (", " ++) enumeratedVars) ++ "):" + , " return " ++ className ++ "(" ++ intercalate ", " enumeratedVars ++ ")" + ] + where + nameWithUnicode = map toLower (funName r) ++ toOrd (funName r) + className = unkw (funName r) + sentForm = rhsRule r + nvCats = numVars sentForm :: [Either (Cat, Doc) String] + enumeratedVars = [render d | (_, d) <- lefts nvCats] + + +-- Creates a transform for a list rule. +createListTransform :: Rul RFun -> String +createListTransform r = unlines + [ " @v_args(inline=True)" + , " def " ++ map toLower name ++ "(self" ++ + concat (map (", " ++) enumeratedVars) ++ "):" + , " return " ++ args + ] + where + name + | isNilFun r = "nil" ++ (identCat . valCat) r + | isOneFun r = "one" ++ (identCat . valCat) r + | isConsFun r = "cons" ++ (identCat . valCat) r + | otherwise = funName r + + sentForm = rhsRule r + nvCats = numVars sentForm :: [Either (Cat, Doc) String] + enumeratedVars = [render d | (_, d) <- lefts nvCats] + + args :: String + | isNilFun r = "[]" + | isOneFun r = "[" ++ head enumeratedVars ++ "]" + | isConsFun r = "[" ++ head enumeratedVars ++ "] + " ++ + last enumeratedVars + | otherwise = error "Should be a list function" + + +-- Creates the transformer functions for the tokens. +createTokenTransformers :: CF -> String +createTokenTransformers cf = unlines $ concat + [ + ifC catString [createTokenTransform "String"] + , ifC catChar [createTokenTransform "Char"] + , ifC catDouble [createTokenTransform "Double"] + , ifC catInteger [createTokenTransform "Integer"] + , userDefTokens + , ifC catIdent [createTokenTransform "Ident"] + ] + where + ifC :: TokenCat -> [String] -> [String] + ifC cat s = if isUsedCat cf (TokenCat cat) then s else [] + + userDefTokens :: [String] + userDefTokens = [ + createTokenTransform name | (name, _) <- tokenPragmas cf + ] + + +-- Creates a transform for a token. +createTokenTransform :: String -> String +createTokenTransform name = unlines + [ " @v_args(inline=True)" + , " def " ++ map toUpper name ++ "(self, token):" + , " return " ++ unkw name ++ "(token.value)" + ] + + +-- | Produces the production in the docstring for the parsing definitions. +prodToDocStr ::[Either Cat String] -> String +prodToDocStr [] = "" +prodToDocStr (ec:[]) = ecsToDocStr ec +prodToDocStr (ec:ecs) = + ecsToDocStr ec ++ " " ++ prodToDocStr ecs + + +-- Converts a single element in the production. +ecsToDocStr :: Either Cat String -> String +ecsToDocStr (Left (TokenCat t)) = map toUpper t +ecsToDocStr (Left c) = map toLower (translateToList (show c)) +ecsToDocStr (Right strOp) = "\"" ++ concat (map escapeBackslash strOp) ++ "\"" + + +-- | For single-line comments +createLineCommentMatcher :: String -> String +createLineCommentMatcher r = unlines + [ " C" ++ toOrd r ++ ": /" ++ concat (map escapeChar r) ++ "[^\\n]*/" + , " %ignore C" ++ toOrd r + ] + + +-- | For multi-line comments +createMultiLineCommentMatcher :: (String, String) -> String +createMultiLineCommentMatcher (s, e) = unlines + [ " C" ++ toOrd (s ++ e) ++ ": /" ++ escaped s ++ "([\\s\\S]*?)" ++ + escaped e ++ "/" + , " %ignore C" ++ toOrd (s ++ e) + ] + where + escaped s = concat $ map escapeChar s + + +-- Since we're using a real string for the grammar, r""" ... """ it seems +-- we can't escape everything in strOp from regflex. Only backslashes. +escapeBackslash :: Char -> String +escapeBackslash '\\' = "\\\\" +escapeBackslash c = [c] + + +-- | To compare names for defines. The first letter needs to be lowered, so +-- "while" == "While". +nameCorresponds :: String -> String -> Bool +nameCorresponds (x:xs) (y:ys) = (toLower x == toLower y) && (xs == ys) +nameCorresponds _ _ = error "Names can't be empty" + + +-- Creates a transformer for a rule with its corresponding define. +makeDefineTransform :: (Int, Rul RFun, Define) -> String +makeDefineTransform (n, defRule, defi) = unlines + [ " @v_args(inline=True)" + , " def d" ++ show n ++ "_r_" ++ map toLower name ++ "(self" ++ + concat (map (", " ++) enumeratedVars) ++ "):" + , " return d_" ++ name ++ "(" ++ intercalate ", " enumeratedVars ++ ")" + , "" + ] + where + name = (wpThing . defName) defi + sentForm = rhsRule defRule + nvCats = numVars sentForm :: [Either (Cat, Doc) String] + enumeratedVars = [render d | (_, d) <- lefts nvCats] + + +-- | Converts the production of a define, called an expression, to a +-- production for the parsing definition. +expToDef :: CF -> Exp -> String +expToDef cf (App "(:)" _ (e:[App "[]" _ _])) = expToDef cf e ++ "]" +expToDef cf (App "(:)" _ (e:[recList])) = "[" ++ expToDef cf e ++ ", " ++ + expToDef cf recList +expToDef _ (App "[]" _ _) = "[]" +expToDef cf (App fName _ exps) + | isLower (head fName) = + "d_" ++ fName ++ "(" ++ addCommas (map (expToDef cf) exps) ++ ")" + | otherwise = + unkw fName ++ "(" ++ addCommas (map (expToDef cf) exps) ++ ")" +expToDef _ (Var s) = unkw s +expToDef _ (LitInt i) = "Integer(" ++ show i ++ ")" +expToDef _ (LitDouble d) = "Double(" ++ show d ++ ")" +expToDef _ (LitChar s) = "Char(\"" ++ show s ++ "\")" +expToDef _ (LitString s) = "String('" ++ s ++ "')" + + +-- A placeholder variable to store additional information, for say type +-- annotation. +placeholderVariableClass :: String +placeholderVariableClass = unlines + [ "# Placeholder to add additional information to a node in the AST," ++ + " like type information." + , "class _AnnType:" + , " def __init__(self):" + , " self.__v = None" + , "" + , " def s(self, val):" + , " if not self.__v == None:" + , " if self.__v != val:" + , " raise Exception('already has type: ' + str(self.__v)" ++ + " + ' and tried to set to ' + str(val))" + , " self.__v = val" + , "" + , " def g(self):" + , " return self.__v" + , "" + , " def __str__(self):" + , " return str(self.__v.__class__)" + , "" + , " def __repr__(self):" + , " return str(self.__v.__class__)" + ] + + +-- | The value categories become abstract classes, for type hinting. +createValueCatClass :: String -> String +createValueCatClass s = "class " ++ s ++ ":\n\tpass\n" + + +-- | Make a Python class from a rule's name and production. +makePythonClass :: Rul RFun -> String +makePythonClass rule = + "@dataclass\n" ++ + "class " ++ className ++ ":\n" ++ + if length cats == 0 then "\tpass\n" else classBody + where + className = unkw (funName rule) + sentForm = rhsRule rule + cats = lefts sentForm + nvCats = numVars sentForm :: [Either (Cat, Doc) String] + + enumeratedVarsWithType = [render d ++ ": " ++ + strCatToPyTyping (show (normCat c)) | (c, d) <- lefts nvCats] + + classBody = unlines $ map ("\t" ++) (enumeratedVarsWithType ++ + ["_ann_type: _AnnType = field(default_factory=_AnnType)"]) + + +-- | Creates the corresponding type hinting for some member variable. +strCatToPyTyping :: String -> String +strCatToPyTyping s = if strIsList s + then "_List['" ++ (unkw . tail . init) s ++ "']" + else unkw s + + +-- | Creates functions for the defines. +createDefineFunctions :: CF -> String +createDefineFunctions cf = unlines + (map (createDefineFunction cf) (definitions cf)) + + +createDefineFunction :: CF -> Define -> String +createDefineFunction cf d = unlines + [ "def d_" ++ (wpThing . defName) d ++ "(" ++ addCommas args ++ "):" + , " return " ++ expToDef cf (defBody d) + ] + where + args = map (unkw . fst) (defArgs d) + diff --git a/source/src/BNFC/Backend/Python/CFtoPyPrettyPrinter.hs b/source/src/BNFC/Backend/Python/CFtoPyPrettyPrinter.hs new file mode 100644 index 00000000..352f12c1 --- /dev/null +++ b/source/src/BNFC/Backend/Python/CFtoPyPrettyPrinter.hs @@ -0,0 +1,406 @@ + +{- + BNF Converter: Python pretty-printer generator + Copyright (C) 2024 Author: Bjorn Werner + Based on CFtoCPrinter.hs, Copyright (C) 2004 Michael Pellauer +-} + +module BNFC.Backend.Python.CFtoPyPrettyPrinter ( cf2PyPretty ) where +import Data.List ( intercalate, nub ) +import BNFC.CF +import BNFC.Backend.Python.PyHelpers +import BNFC.Backend.Common.NamedVariables +import Text.PrettyPrint (Doc, render) +import Data.Either (lefts) +import BNFC.Backend.Common.StrUtils +import qualified Data.List.NonEmpty as List1 + +-- | Used to create PrettyPrinter.py, that contains the functionality +-- to print the AST and the linearized tree. +cf2PyPretty :: String -> CF -> String +cf2PyPretty pkgName cf = unlines + [ "from " ++ pkgName ++ ".Absyn import *" + , "" + , makePrintAST cf + , "" + , makeListDecons cf + , "" + , makeRenderC + , "" + , makeCoercCompare cf + , "" + , makeCompareFunc + , "" + , makeLinFunc cf + ] + + +-- | Creates the print AST function. +makePrintAST :: CF -> String +makePrintAST cf = concat + [ "def printAST(ast: object) -> list:\n" + , " match ast:\n" + , concat + [ ifUsedThen catInteger + [ " case Integer():" + , " return str(ast)" + ] + , ifUsedThen catDouble + [ " case Double():" + , " if ast.is_integer():" + , " return str(int(ast))" + , " else:" + , " return str(ast)" + ] + , ifUsedThen catString + [ " case String():" + , " return str(ast)" + ] + , ifUsedThen catChar + [ " case Char():" + , " return str(ast)" + ] + , ifUsedThen catIdent + [ " case Ident():" + , " return '\"' + str(ast) + '\"'" + ] + ] + , if length (tokenNames cf) > 0 + then unlines + [ " case (" ++ intercalate " | " + (map ((++ "()") . unkw) (tokenNames cf)) ++ "):" + , " return '\"' + str(ast) + '\"'" + ] + else "" + , " case list():\n" + , " return '[' + ', '.join([printAST(a) for a in ast]) + ']'\n" + , "\n" + , " if len(vars(ast)) > 0:\n" + , " return '(' + ast.__class__.__name__ + ' ' + ' '.join(" ++ + "[printAST(vars(ast)[k]) for k in vars(ast) if k != '_ann_type']) + ')'\n" + , " else:\n" + , " return ast.__class__.__name__\n" + ] + where + ifUsedThen :: TokenCat -> [String] -> String + ifUsedThen cat ss + | isUsedCat cf (TokenCat cat) = unlines ss + | otherwise = "" + + +-- Creates deconstructors for all list categories. +makeListDecons :: CF -> String +makeListDecons cf = unlines $ map (makeListDecon cf) listCats + where + rules = cfgRules cf + valCats = nub $ map valCat rules + listCats = [c | c <- valCats, isList c] + + +-- Creates a deconstructor for some list category. +makeListDecon :: CF -> Cat -> String +makeListDecon cf c = concat + [ "def list" ++ name ++ "Decon(xs):\n" + , oneRuleStr + , nilRuleStr + , consRuleStr + , "\n" + ] + where + name = show $ catOfList c + listRulesForCat = [ r | r <- cfgRules cf, isParsable r, valCat r == c] + + nilRule = case [r | r <- listRulesForCat, isNilFun r] of + [] -> Nothing + rs -> Just (head rs) + oneRule = case [r | r <- listRulesForCat, isOneFun r] of + [] -> Nothing + rs -> Just (head rs) + consRule = case [r | r <- listRulesForCat, isConsFun r] of + [] -> Nothing + rs -> Just (head rs) + + -- List rules are of the form: + -- [C] ::= symbols.. C symbols.. [C] + -- The production, in Python, is concatenated recursively: + -- symbols.. + c(xs[0], 'C1') + symbols.. + listCDecon(xs[1:]) + symbols.. + sentFormToArgs :: Int -> [Either Cat String] -> String + sentFormToArgs _ [] = "[]" + sentFormToArgs v (Right strOp:ecss) = + "['" ++ escapeChars strOp ++ "'] + " ++ + sentFormToArgs v ecss + sentFormToArgs v (Left _:ecss) + | v == 0 = "c(xs[0], '" ++ name ++ "') + " ++ sentFormToArgs (v+1) ecss + | v == 1 = "list" ++ name ++ "Decon(xs[1:]) + " ++ + sentFormToArgs (v+1) ecss + | otherwise = error "A list production can max have C and [C]." + + nilRuleStr = case nilRule of + Nothing -> "" + Just r -> unlines + [ " if len(xs) == 0:" + , " return " ++ sentFormToArgs 0 (rhsRule r) + ] + + oneRuleStr = case oneRule of + Nothing -> "" + Just r -> unlines + [ " if len(xs) == 1:" + , " return " ++ sentFormToArgs 0 (rhsRule r) + ] + + consRuleStr = case consRule of + Nothing -> "" + Just r -> " return " ++ sentFormToArgs 0 (rhsRule r) ++ "\n" + + +-- | Creates the renderC function, which creates a string of a list of +-- strings, and inserts white-spaces to render the language in a C-like +-- manner. +makeRenderC :: String +makeRenderC = unlines + [ "def renderC(ss: list):" + , " def br(i):" + , " return '\\n' + ' ' * iLevel" + , "" + , " def ident(i):" + , " return ' ' * iLevel" + , "" + , " return tot[:i]" + , "" + , " def oneEmptyLine(tot):" + , " tot = tot.rstrip(' ')" + , " if len(tot) > 0 and tot[-1] != '\\n':" + , " tot += '\\n'" + , " tot += ident(iLevel)" + , " return tot" + , "" + , " tot = ''" + , " iLevel = 0" + , " for i in range(len(ss)):" + , " s = ss[i]" + , " match s:" + , " case '{':" + , " tot = oneEmptyLine(tot)" + , " iLevel += 1" + , " tot += '{' + br(iLevel)" + , " case ('(' | '['):" + , " tot += s" + , " case (')' | ']'):" + , " tot = tot.rstrip()" + , " tot += s + ' '" + , " case '}':" + , " iLevel -= 1" + , " tot = oneEmptyLine(tot)" + , " tot += s + br(iLevel)" + , " case ',':" + , " tot = tot.rstrip()" + , " tot += s + ' '" + , " case ';':" + , " tot = tot.rstrip()" + , " tot += s + br(iLevel)" + , " case '':" + , " tot += ''" + , " case ' ':" + , " tot += s" + , " case _:" + , " if s[-1] == ' ':" -- To not extend separators of spaces. + , " tot = tot.rstrip()" + , " tot += s" + , " else:" + , " tot += s + ' '" + , "" + , " return tot" + ] + + +-- Provides a mapping from a rule to its value category. +makeCoercCompare :: CF -> String +makeCoercCompare cf = concat + [ "cdict = {\n" + , unlines (map (\(fs, cs) -> " " ++ unkw fs ++ " : '" ++ cs ++ "',") scs) + , "}" + ] + where + scs :: [(String, String)] + scs = [(funName r, (show . wpThing . valRCat) r) | r <- cfgRules cf, + not (isCoercion r), not (isNilCons r), not (isDefinedRule r)] + + +-- | Creates a function that attempts to figure out if +-- parentheses are required, for example: +-- 1 + (2 * 3) +-- The precedence for the addition is low, say Exp, but the multiplication +-- has a higher precedence, say Exp1, so parantheses are needed. +makeCompareFunc :: String +makeCompareFunc = unlines + [ "def c(ast, cat: str) -> list:" + , " cl = ast.__class__" + , " if cl in cdict:" + , " clCat = cdict[cl]" + , " clCatAlphas = ''.join(filter(str.isalpha, clCat))" + , " catAlphas = ''.join(filter(str.isalpha, cat))" + , " clCatNums = ''.join(filter(str.isnumeric, clCat))" + , " catNums = ''.join(filter(str.isnumeric, cat))" + , " clCatNum = 0" + , " catNum = 0" + , " if clCatAlphas == catAlphas:" + , " if len(clCatNums) > 0:" + , " clCatNum = int(clCatNums)" + , " if len(catNums) > 0:" + , " catNum = int(catNums)" + , " if clCatNum < catNum:" + , " return ['('] + lin(ast) + [')']" + , " return lin(ast)" + ] + + +-- | Returns the AST as a list of characters, which can be sent into the +-- renderC.function. +makeLinFunc :: CF -> String +makeLinFunc cf = unlines + [ "def lin(ast: object) -> list:" + , " match ast:" + , concat + [ ifUsedThen catInteger + [ " case Integer():" + , " return [str(ast)]" + ] + , ifUsedThen catDouble + [ " case Double():" + , " if ast.is_integer():" + , " return [str(int(ast))]" + , " else:" + , " return [str(ast)]" + ] + , ifUsedThen catString + [ " case String():" + , " return [ast]" + ] + , ifUsedThen catIdent + [ " case Ident():" + , " return [ast]" + ] + , ifUsedThen catChar + [ " case Char():" + , " return [ast]" + ] + ] + , " # skeleTokenCases:" + , unlines skeleTokenCases + , " # skeleRuleCases:" + , unlines skeleRuleCases + , -- Deals with cases where the entrypoint is say [Stm] or [Exp], + -- with pattern matching on the first object in the list. + " case " ++ "list():" + , " if len(ast) == 0:" + , " return []" + , " else:" + , " match ast[0]:" + , unlines listEntrypointCases + , " case _:" + , " raise Exception(ast[0].__class__.__name__, " ++ + "'unmatched ast[0]')" + , " case _:" + , " raise Exception(str(ast.__class__) + ' unmatched')" + ] + where + -- Used to include standard literals, if needed. + ifUsedThen :: TokenCat -> [String] -> String + ifUsedThen cat ss + | isUsedCat cf (TokenCat cat) = unlines ss + | otherwise = "" + + -- Figures out the deliminators for the separators and terminators, + -- to further process a deconstructed object that contains list(s). + rules = [r | r <- cfgRules cf + , not (isCoercion r) + , not (isDefinedRule r) + , not (isNilCons r) + ] + + skeleTokenCases = map makeSkeleTokenCase (tokenNames cf) + skeleRuleCases = map makeSkeleRuleCase rules + + catEntrypointsForLists = + [catOfList c | c <- (List1.toList . allEntryPoints) cf, isList c] + + -- The Haskell backend defaults to the production for the lowest + -- precedence for lists that are defined. Like ``separator Exp1 ","``. + lowestPrecListCats = [c | c <- catEntrypointsForLists, + precCat c == (minimum (map precCat + [c2 | c2 <- catEntrypointsForLists, normCat c == normCat c2] + ) + ) + ] + + listEntrypointCases = + map (makeListEntrypointCase cf) lowestPrecListCats + + +-- | Creates cases that checks what class individual nodes might be, meaning +-- the rule names, or the token categories +makeListEntrypointCase :: CF -> Cat -> String +makeListEntrypointCase cf c = concat + [ " case " ++ intercalate "|" constructors ++ ":\n" + , " return list" ++ show c ++ "Decon(ast)" + ] + where + constructors = if isTokenCat c + then [unkw (show c) ++ "()"] + else map ((++ "()") . unkw . funName) + [ + r | r <- rulesForNormalizedCat cf (normCat c), + not (isCoercion r), + not (isDefinedRule r) + ] + + +-- Creates a case for a user defined literal, which inherits str. +makeSkeleTokenCase :: String -> String +makeSkeleTokenCase tokenName = concat + [ " case " ++ unkw tokenName ++ "():\n" + , " return [ast]" + ] + + +-- | Creates a case for some rule, with the additional information of what +-- separator- and terminator-delimiters there are. +makeSkeleRuleCase :: Rul RFun -> String +makeSkeleRuleCase rule = concat + [ " case " ++ unkw fName ++ "(" ++ varNamesCommad ++ "):\n" + , " # " ++ (showEcss sentForm) ++ "\n" + , " return " ++ if (length args > 0) + then (intercalate " + " args) + else "[]" + ] + where + fName = wpThing (funRule rule) + sentForm = rhsRule rule + + nvCats = numVars sentForm :: [Either (Cat, Doc) String] + enumeratedVarNames = [render d | (_, d) <- lefts nvCats] + + varNamesCommad = if length enumeratedVarNames > 0 + then addCommas (enumeratedVarNames ++ ["_ann_type"]) + else "" + + args = ecssAndVarsToList + sentForm + enumeratedVarNames + + +-- | Creates a list of a production with both terminals and non-terminals. +ecssAndVarsToList :: [Either Cat String] -> [String] -> [String] +ecssAndVarsToList [] _ = [] +ecssAndVarsToList (Left c:ecss) (s:ss) + | isList c = ["list" ++ name ++ "Decon(" ++ s ++ ")"] ++ + ecssAndVarsToList ecss ss + | otherwise = ["c(" ++ s ++ ", '" ++ (show c) ++ "')"] ++ + ecssAndVarsToList ecss ss + where + name = show $ catOfList c +ecssAndVarsToList (Right strOp:ecss) ss = + ["['" ++ escapeChars strOp ++ "']"] ++ ecssAndVarsToList ecss ss +ecssAndVarsToList ((Left _):_) [] = error "Missing variable name" + diff --git a/source/src/BNFC/Backend/Python/CFtoPySkele.hs b/source/src/BNFC/Backend/Python/CFtoPySkele.hs new file mode 100644 index 00000000..26904764 --- /dev/null +++ b/source/src/BNFC/Backend/Python/CFtoPySkele.hs @@ -0,0 +1,109 @@ + +{- + BNF Converter: Python skeleton-code generator + Copyright (C) 2024 Author: Bjorn Werner +-} + +module BNFC.Backend.Python.CFtoPySkele where +import BNFC.CF +import BNFC.Backend.Python.PyHelpers +import Data.Char (toLower) +import BNFC.Backend.Common.NamedVariables +import Text.PrettyPrint (Doc, render) +import Data.Either (lefts) +import Data.List (intercalate) + +-- | Entrypoint. +cf2PySkele :: String -> CF -> String +cf2PySkele pkgName cf = unlines + ["from " ++ pkgName ++ ".Absyn import *" + , "" + , "" + , makeSkele cf + ] + + +-- Creates first a matcher with all value categories, and underneath one +-- matcher for each value category. +makeSkele :: CF -> String +makeSkele cf = unlines + [ "# Categories combined into one matcher" + , "def skeleMatcher(ast: object):" + , ind 1 "match ast:" + , intercalate "\n" skeleLiteralCases + , intercalate "\n" skeleTokenCases + , intercalate "\n" skeleRuleCases + , ind 2 "case _:" + , ind 3 "raise Exception(str(ast.__class__) + ' unmatched')" + , "" + , "" + , "# Categories split into their own matchers" + , unlines matchersOnCats + ] + where + rules = + [ r | r <- cfgRules cf + , not (isCoercion r) + , not (isDefinedRule r) + , not (isNilCons r) + ] + + presentLiterals = ifC catInteger ++ + ifC catDouble ++ + ifC catString ++ + ifC catIdent ++ + ifC catChar + + skeleLiteralCases = map makeSkeleTokenCase presentLiterals + skeleTokenCases = map makeSkeleTokenCase (tokenNames cf) + skeleRuleCases = map makeSkeleRuleCase rules + + parserCats = filter (not . isList) (allParserCatsNorm cf) :: [Cat] + rulesfornormalizedcat = map (rulesForNormalizedCat cf) parserCats + parserCatsWithRules = zip parserCats rulesfornormalizedcat + + matchersOnCats = map makeMatcherOnCat parserCatsWithRules + + ifC :: TokenCat -> [String] + ifC cat = if isUsedCat cf (TokenCat cat) then [cat] else [] + + +-- Creates a matcher for some value category. +makeMatcherOnCat :: (Cat, [Rul RFun]) -> String +makeMatcherOnCat (c, rules) = unlines + [ "def matcher" ++ show c ++ "(" ++ varName ++ ": " ++ show c ++ "):" + , ind 1 "match " ++ varName ++ ":" + , intercalate "\n" cases + , ind 2 "case _:" + , ind 3 "raise Exception(str(" ++ varName ++ ".__class__) + ' unmatched')" + , "" + ] + where + varName = map toLower (show c) ++ "_" + cases = map makeSkeleRuleCase (filter + (\r -> not (isCoercion r) && not (isDefinedRule r)) + rules) + + +-- | Creates a case for some rule. +makeSkeleRuleCase :: Rul RFun -> String +makeSkeleRuleCase rule = intercalate "\n" + [ ind 2 "case " ++ name ++ "(" ++ varNamesCommad ++ "):" + , ind 3 "# " ++ (showEcss sentForm) + , ind 3 "raise Exception('" ++ name ++ " not implemented')" + ] + where + name = unkw (funName rule) + sentForm = rhsRule rule + nvCats = numVars sentForm :: [Either (Cat, Doc) String] + enumeratedVarNames = [render d | (_, d) <- lefts nvCats] + varNamesCommad = addCommas (enumeratedVarNames ++ ["_ann_type"]) + + +-- | Creates a case for a user-defined token. +makeSkeleTokenCase :: String -> String +makeSkeleTokenCase tokenName = intercalate "\n" + [ ind 2 "case " ++ unkw tokenName ++ "():" + , ind 3 "raise Exception('" ++ unkw tokenName ++ " not implemented')" + ] + diff --git a/source/src/BNFC/Backend/Python/PyHelpers.hs b/source/src/BNFC/Backend/Python/PyHelpers.hs new file mode 100644 index 00000000..f68abe13 --- /dev/null +++ b/source/src/BNFC/Backend/Python/PyHelpers.hs @@ -0,0 +1,136 @@ + +{- + BNF Converter: Python backend helper functions + Copyright (C) 2024 Author: Bjorn Werner +-} + +module BNFC.Backend.Python.PyHelpers where +import Data.List ( intercalate ) +import Data.Char +import BNFC.CF + + +-- Indents by four spaces +ind :: Int -> String -> String +ind 0 s = s +ind n s = ind (n-1) (" " ++ s) + + +addCommas :: [String] -> String +addCommas ss = intercalate ", " ss + + +addCitationSigns :: String -> String +addCitationSigns ss = "'" ++ ss ++ "'" + + +filterOut :: Eq a => [a] -> [a] -> [a] +filterOut xs ys = filter (\x -> not (elem x ys)) xs + + +-- Converts every character to unicode with an underscore in front. +toOrd :: String -> String +toOrd s = concat (map (("_" ++) . show . ord) s) + + +-- | Converts a string of underscores and unicode numbers such as "_53_53" +-- into "++". +toChr :: String -> String +toChr "" = "" +toChr xs = map chr nrs + where + nrsStr = tail $ split '_' xs :: [String] + nrs = map read nrsStr :: [Int] + + +split :: Char -> String -> [String] +split c s = split' c s "" + + +split' :: Char -> String -> String -> [String] +split' _ [] ps = [ps] +split' c (s:ss) ps + | c == s = [ps] ++ split' c ss "" + | otherwise = split' c ss (ps ++ [s]) + + +-- Converts [Cat] into ListCat, which is mainly used in the parser. +translateToList :: String -> String +translateToList s + | strIsList s = "List" ++ (tail $ init s) + | otherwise = s + + +strIsList :: String -> Bool +strIsList s = head s == '[' && last s == ']' + + +firstRight :: [Either a b] -> Maybe b +firstRight [] = Nothing +firstRight (Left _:es) = firstRight es +firstRight (Right r:_) = Just r + + +-- Retrieves the first character from strings such as "[Stm]" or "Stm". +firstAlpha :: String -> Char +firstAlpha s + | strIsList s = head $ tail s + | otherwise = head s + + +-- | Converts a production into a string, for comments. +showEcss :: [Either Cat String] -> String +showEcss [] = "" +showEcss (Left c:ecss) = show c ++ " " ++ (showEcss ecss) +showEcss (Right strOp:ecss) = "\"" ++ strOp ++ "\" " ++ (showEcss ecss) + + +-- | Adds an underscore if the string overlaps with a keyword. +unkw :: String -> String +unkw s = if s `elem` kwListWithSoftKeywords then s ++ "_" else s + + +-- To add an extra underscore if something overlaps with a keyword. +kwListWithSoftKeywords :: [String] +kwListWithSoftKeywords = + [ "False" + , "None" + , "True" + , "and" + , "as" + , "assert" + , "async" + , "await" + , "break" + , "class" + , "continue" + , "def" + , "del" + , "elif" + , "else" + , "except" + , "finally" + , "for" + , "from" + , "global" + , "if" + , "import" + , "in" + , "is" + , "lambda" + , "nonlocal" + , "not" + , "or" + , "pass" + , "raise" + , "return" + , "try" + , "while" + , "with" + , "yield" + , "_" + , "case" + , "match" + , "type" + ] + diff --git a/source/src/BNFC/Backend/Python/RegToFlex.hs b/source/src/BNFC/Backend/Python/RegToFlex.hs new file mode 100644 index 00000000..37e357b4 --- /dev/null +++ b/source/src/BNFC/Backend/Python/RegToFlex.hs @@ -0,0 +1,97 @@ +{-# LANGUAGE LambdaCase #-} + +{- + Due to the almost full similarity, the name RegToFlex remains from the + C backend (2024). +-} + +module BNFC.Backend.Python.RegToFlex (printRegFlex, escapeChar) where + +-- modified from pretty-printer generated by the BNF converter + +import Data.Char (ord, showLitChar) +import qualified Data.List as List +import BNFC.Abs (Reg(..), Identifier(Identifier)) +import BNFC.Backend.Common (flexEps) + + +-- the top-level printing method +printRegFlex :: Reg -> String +printRegFlex = render . prt 0 + + +-- you may want to change render and parenth +render :: [String] -> String +render = rend (0::Int) where + rend i ss = case ss of + "[" :ts -> cons "[" $ rend i ts + "(" :ts -> cons "(" $ rend i ts + t : "," :ts -> cons t $ space "," $ rend i ts + t : ")" :ts -> cons t $ cons ")" $ rend i ts + t : "]" :ts -> cons t $ cons "]" $ rend i ts + t :ts -> space t $ rend i ts + _ -> "" + cons s t = s ++ t + space t s = if null s then t else t ++ s + + +parenth :: [String] -> [String] +parenth ss = ["("] ++ ss ++ [")"] + + +-- the printer class does the job +class Print a where + prt :: Int -> a -> [String] + + +prPrec :: Int -> Int -> [String] -> [String] +prPrec i j = if j prPrec i 2 (concat [prt 2 reg0 , prt 3 reg]) + RAlt reg0 reg -> prPrec i 1 (concat [prt 1 reg0 , ["|"] , prt 2 reg]) + + -- Flex does not support set difference. See link for valid patterns. + -- https://westes.github.io/flex/manual/Patterns.html#Patterns + -- RMinus reg0 reg -> prPrec i 1 (concat [prt 2 reg0 , ["#"] , prt 2 reg]) + RMinus reg0 REps -> prt i reg0 -- REps is identity for set difference + RMinus RAny (RChar c) -> [ concat [ "[^", escapeChar c, "]" ] ] + RMinus RAny (RAlts str) -> [ concat [ "[^", concatMap escapeChar str, "]" ] ] + -- FIXME: unicode inside brackets [...] is not accepted by flex + -- FIXME: maybe we could add cases for char - RDigit, RLetter etc. + RMinus _ _ -> error "Flex does not support general set difference" + + RStar reg -> concat [ prt 3 reg , ["*"] ] + RPlus reg -> concat [ prt 3 reg , ["+"] ] + ROpt reg -> concat [ prt 3 reg , ["?"] ] + REps -> [ flexEps ] + RChar c -> [ escapeChar c ] + -- Unicode characters cannot be inside [...] so we use | instead. + RAlts str -> prPrec i 1 $ List.intersperse "|" $ map escapeChar str + -- RAlts str -> concat [["["], prt 0 $ concatMap escapeChar str, ["]"]] + RSeqs str -> prPrec i 2 $ map escapeChar str + RDigit -> [ "\\d" ] + RLetter -> [ "[A-Za-z]" ] -- add underscore ? + RUpper -> [ "[A-Z]" ] + RLower -> [ "[a-z]" ] + RAny -> [ "." ] + + +-- | Handle special characters in regular expressions. +escapeChar :: Char -> String +escapeChar c + | c `elem` reserved = '\\':[c] + | let x = ord c, x >= 256 = [c] + -- keep unicode characters -- "\x" ++ showHex x "" + | otherwise = showLitChar c "" + where + reserved :: String + reserved = " '$+-*=<>[](){}!?.,;:^~|&%#/\\$_@\"" + + diff --git a/source/src/BNFC/Options.hs b/source/src/BNFC/Options.hs index ac5fdbf6..74a1c757 100644 --- a/source/src/BNFC/Options.hs +++ b/source/src/BNFC/Options.hs @@ -64,6 +64,7 @@ data Target = TargetC | TargetCpp | TargetCppNoStl | TargetHaskell | TargetHaskellGadt | TargetLatex | TargetJava | TargetOCaml | TargetPygments | TargetTreeSitter + | TargetPython | TargetCheck deriving (Eq, Bounded, Enum, Ord) @@ -83,6 +84,7 @@ instance Show Target where show TargetPygments = "Pygments" show TargetTreeSitter = "Tree-sitter" show TargetCheck = "Check LBNF file" + show TargetPython = "Python" -- | Which version of Alex is targeted? data AlexVersion = Alex3 @@ -261,6 +263,7 @@ printTargetOption = ("--" ++) . \case TargetOCaml -> "ocaml" TargetPygments -> "pygments" TargetTreeSitter -> "tree-sitter" + TargetPython -> "python" TargetCheck -> "check" printAlexOption :: AlexVersion -> String @@ -314,6 +317,8 @@ targetOptions = "Output a Python lexer for Pygments" , Option "" ["tree-sitter"] (NoArg (\o -> o {target = TargetTreeSitter})) "Output grammar.js file for use with tree-sitter" + , Option "" ["python"] (NoArg (\ o -> o{target = TargetPython })) + "Output Python code for use with PLY" , Option "" ["check"] (NoArg (\ o -> o{target = TargetCheck })) "No output. Just check input LBNF file" ] @@ -530,6 +535,7 @@ instance Maintained Target where TargetOCaml -> True TargetPygments -> True TargetTreeSitter -> True + TargetPython -> True TargetCheck -> True instance Maintained AlexVersion where @@ -661,4 +667,5 @@ translateOldOptions = mapM $ \ o -> do , ("--ghc" , "--generic") , ("--deriveGeneric" , "--generic") , ("--deriveDataTypeable" , "--generic") + , ("-python" , "--python") ] diff --git a/testing/src/ParameterizedTests.hs b/testing/src/ParameterizedTests.hs index ce0c945c..8231c8eb 100644 --- a/testing/src/ParameterizedTests.hs +++ b/testing/src/ParameterizedTests.hs @@ -421,6 +421,10 @@ parameters = concat , javaParams { tpName = "Java (with jflex and line numbers)" , tpBnfcOptions = ["--java", "--jflex", "-l"] } ] + -- Python + , [ pythonParams { tpName = "Python" + , tpBnfcOptions = ["--python"] } + ] ] where base = baseParameters @@ -444,6 +448,14 @@ parameters = concat , tpBnfcOptions = ["--ocaml"] , tpRunTestProg = haskellRunTestProg } + pythonParams = base + { tpBuild = do + return () -- nothing to make or compile + , + tpRunTestProg = \ _lang args -> do + pyFile_ <- findFile "genTest.py" + cmd "python3" $ pyFile_ : args + } -- | Helper function that runs bnfc with the context's options and an -- option to generate 'tpMakefile'.