Skip to content

Commit

Permalink
Update C++ Abs files and Printer class
Browse files Browse the repository at this point in the history
  • Loading branch information
hangingman committed Nov 10, 2021
1 parent ccfadf4 commit 6058374
Show file tree
Hide file tree
Showing 5 changed files with 93 additions and 69 deletions.
80 changes: 49 additions & 31 deletions source/src/BNFC/Backend/CPP/Makefile.hs
Original file line number Diff line number Diff line change
@@ -1,22 +1,27 @@
{-# LANGUAGE OverloadedStrings #-}

module BNFC.Backend.CPP.Makefile (makefile) where

import BNFC.Options
import BNFC.Backend.Common.Makefile
import BNFC.PrettyPrint
import BNFC.Utils (when)

makefile :: String -> String -> String -> String -> String -> String -> Doc
makefile prefix name compileOpt lexerExt parserExt basename = vcat
makefile :: String -> String -> SharedOptions -> String -> Doc
makefile prefix name opts basename =
vcat $
[ mkVar "CC" "g++ -g"
, mkVar "CCFLAGS" (compileOpt ++ " -W -Wall -Wno-unused-parameter -Wno-unused-function -Wno-unneeded-internal-declaration")
, mkVar "CCFLAGS" (compileOpt ++ " -W -Wall -Wsign-conversion -Wno-unused-parameter -Wno-unused-function -Wno-unneeded-internal-declaration")
, ""
, mkVar "FLEX" "flex"
, mkVar "FLEX_OPTS" ("-P" ++ prefix)
, ""
, mkVar "BISON" "bison"
, mkVar "BISON_OPTS" ("-t -p" ++ prefix)
, ""
, mkVar "OBJS" "Absyn.o Buffer.o Lexer.o Parser.o Printer.o"
, if (ansi opts /= Ansi) then
mkVar "OBJS" "Absyn.o Buffer.o Lexer.o Parser.o Driver.o Printer.o"
else
mkVar "OBJS" "Absyn.o Buffer.o Lexer.o Parser.o Printer.o"
, ""
, mkRule ".PHONY" ["clean", "distclean"]
[]
Expand All @@ -28,38 +33,51 @@ makefile prefix name compileOpt lexerExt parserExt basename = vcat
[ name ++ e | e <- [".aux", ".log", ".pdf",".dvi", ".ps", ""]] ]
, mkRule "distclean" ["clean"]
[ "rm -f " ++ unwords
[ "Absyn.C", "Absyn.H"
, "Buffer.C", "Buffer.H"
, "Test.C"
, "Bison.H", "Parser.C", "Parser.H", "ParserError.H", name ++ parserExt
, "Lexer.C", name ++ lexerExt
, "Skeleton.C", "Skeleton.H"
, "Printer.C", "Printer.H"
[ "Absyn" ++ cppExt, "Absyn" ++ hExt
, "Buffer" ++ cppExt, "Buffer" ++ hExt
, "Test" ++ cppExt
, "Bison" ++ hExt, "Parser" ++ cppExt, "Parser" ++ hExt, "ParserError" ++ hExt, name ++ parserExt
, "Lexer" ++ cppExt, name ++ lexerExt
, "Skeleton" ++ cppExt, "Skeleton" ++ hExt
, "Printer" ++ cppExt, "Printer" ++ hExt
, "Driver" ++ cppExt, "Driver" ++ hExt
, "Scanner" ++ hExt
, "location" ++ hExt
, basename
, name ++ ".tex"
]
]
, mkRule testName [ "${OBJS}", "Test.o" ]
[ "@echo \"Linking " ++ testName ++ "...\""
, "${CC} ${OBJS} Test.o -o " ++ testName ]
, mkRule "Absyn.o" [ "Absyn.C", "Absyn.H" ]
[ "${CC} ${CCFLAGS} -c Absyn.C" ]
, mkRule "Buffer.o" [ "Buffer.C", "Buffer.H" ]
[ "${CC} ${CCFLAGS} -c Buffer.C " ]
, mkRule "Lexer.C" [ name ++ lexerExt ]
[ "${FLEX} ${FLEX_OPTS} -oLexer.C " ++ name ++ lexerExt ]
, mkRule "Parser.C Bison.H" [ name ++ parserExt ]
[ "${BISON} ${BISON_OPTS} " ++ name ++ parserExt ++ " -o Parser.C" ]
, mkRule "Absyn.o" [ "Absyn" ++ cppExt, "Absyn" ++ hExt ]
[ "${CC} ${CCFLAGS} -c Absyn" ++ cppExt ]
, when (ansi opts /= Ansi)
mkRule "Driver.o" [ "Driver" ++ cppExt, "Driver" ++ hExt ]
[ "${CC} ${CCFLAGS} -c Driver" ++ cppExt ]
, mkRule "Buffer.o" [ "Buffer" ++ cppExt, "Buffer" ++ hExt ]
[ "${CC} ${CCFLAGS} -c Buffer" ++ cppExt ]
, mkRule ("Lexer" ++ cppExt) [ name ++ lexerExt ]
[ "${FLEX} ${FLEX_OPTS} -oLexer" ++ cppExt ++ " " ++ name ++ lexerExt ]
, mkRule ("Parser" ++ cppExt++ " Bison" ++ hExt) [ name ++ parserExt ]
[ "${BISON} ${BISON_OPTS} " ++ name ++ parserExt ++ " -o Parser" ++ cppExt ]
, mkRule "Lexer.o" [ "CCFLAGS+=-Wno-sign-conversion" ]
, mkRule "Lexer.o" [ "Lexer.C", "Bison.H" ]
[ "${CC} ${CCFLAGS} -c Lexer.C " ]
, mkRule "Parser.o" [ "Parser.C", "Absyn.H", "Bison.H" ]
[ "${CC} ${CCFLAGS} -c Parser.C" ]
, mkRule "Printer.o" [ "Printer.C", "Printer.H", "Absyn.H" ]
[ "${CC} ${CCFLAGS} -c Printer.C" ]
, mkRule "Skeleton.o" [ "Skeleton.C", "Skeleton.H", "Absyn.H" ]
[ "${CC} ${CCFLAGS} -Wno-unused-parameter -c Skeleton.C" ]
, mkRule "Test.o" [ "Test.C", "Parser.H", "Printer.H", "Absyn.H" ]
[ "${CC} ${CCFLAGS} -c Test.C" ]
[]
, mkRule "Lexer.o" [ "Lexer" ++ cppExt, "Bison" ++ hExt ]
[ "${CC} ${CCFLAGS} -c Lexer" ++ cppExt ]
, mkRule "Parser.o" [ "Parser" ++ cppExt, "Absyn" ++ hExt, "Bison" ++ hExt ]
[ "${CC} ${CCFLAGS} -c Parser" ++ cppExt ]
, mkRule "Printer.o" [ "Printer" ++ cppExt, "Printer" ++ hExt, "Absyn" ++ hExt ]
[ "${CC} ${CCFLAGS} -c Printer" ++ cppExt ]
, mkRule "Skeleton.o" [ "Skeleton" ++ cppExt, "Skeleton" ++ hExt, "Absyn" ++ hExt ]
[ "${CC} ${CCFLAGS} -Wno-unused-parameter -c Skeleton" ++ cppExt ]
, mkRule "Test.o" [ "Test" ++ cppExt, "Parser" ++ hExt, "Printer" ++ hExt, "Absyn" ++ hExt ]
[ "${CC} ${CCFLAGS} -c Test" ++ cppExt ]
]
where testName = "Test" ++ name
where
testName = "Test" ++ name
compileOpt = if Ansi == ansi opts then "--ansi" else "-std=c++14"
lexerExt = if Ansi == ansi opts then ".l" else ".ll"
parserExt = if Ansi == ansi opts then ".y" else ".yy"
cppExt = if Ansi == ansi opts then ".c" else ".cc"
hExt = if Ansi == ansi opts then ".h" else ".hh"
2 changes: 1 addition & 1 deletion source/src/BNFC/Backend/CPP/NoSTL.hs
Original file line number Diff line number Diff line change
Expand Up @@ -37,7 +37,7 @@ makeCppNoStl opts cf = do
let (skelH, skelC) = cf2CVisitSkel False Nothing cf
mkCppFile "Skeleton.H" skelH
mkCppFile "Skeleton.C" skelC
let (prinH, prinC) = cf2CPPPrinter False Nothing cf
let (prinH, prinC) = cf2CPPPrinter False Nothing cf ".H"
mkCppFile "Printer.H" prinH
mkCppFile "Printer.C" prinC
mkCppFile "Test.C" (cpptest cf)
Expand Down
44 changes: 22 additions & 22 deletions source/src/BNFC/Backend/CPP/PrettyPrinter.hs
Original file line number Diff line number Diff line change
Expand Up @@ -35,12 +35,12 @@ import BNFC.Backend.CPP.STL.STLUtils
import BNFC.PrettyPrint

--Produces (.H file, .C file)
cf2CPPPrinter :: Bool -> Maybe String -> CF -> (String, String)
cf2CPPPrinter useStl inPackage cf =
(mkHFile useStl inPackage cf groups, mkCFile useStl inPackage cf groups)
where
cf2CPPPrinter :: Bool -> Maybe String -> CF -> String -> (String, String)
cf2CPPPrinter useStl inPackage cf hExt =
(mkHFile useStl inPackage cf groups hExt, mkCFile useStl inPackage cf groups hExt)
where
groups = when useStl (positionRules cf) -- CPP/NoSTL treats position tokens as just tokens
++ fixCoercions (ruleGroupsInternals cf)
++ fixCoercions (ruleGroupsInternals cf)

positionRules :: CF -> [(Cat,[Rule])]
positionRules cf =
Expand All @@ -51,8 +51,8 @@ positionRules cf =
{- **** Header (.H) File Methods **** -}

--An extremely large function to make the Header File
mkHFile :: Bool -> Maybe String -> CF -> [(Cat,[Rule])] -> String
mkHFile useStl inPackage cf groups = unlines
mkHFile :: Bool -> Maybe String -> CF -> [(Cat,[Rule])] -> String -> String
mkHFile useStl inPackage cf groups hExt = unlines
[ printHeader
, content
, classFooter
Expand All @@ -67,7 +67,7 @@ mkHFile useStl inPackage cf groups = unlines
"#ifndef " ++ hdef,
"#define " ++ hdef,
"",
"#include \"Absyn.H\"",
"#include \"Absyn" ++hExt++ "\"",
"#include <stdio.h>",
"#include <stddef.h>",
"#include <string.h>",
Expand Down Expand Up @@ -209,8 +209,8 @@ prRuleH _ = ""
{- **** Implementation (.C) File Methods **** -}

--This makes the .C file by a similar method.
mkCFile :: Bool -> Maybe String -> CF -> [(Cat,[Rule])] -> String
mkCFile useStl inPackage cf groups = concat
mkCFile :: Bool -> Maybe String -> CF -> [(Cat,[Rule])] -> String -> String
mkCFile useStl inPackage cf groups hExt = concat
[
header,
nsStart inPackage ++ "\n",
Expand All @@ -231,7 +231,7 @@ mkCFile useStl inPackage cf groups = concat
"/*** Pretty Printer and Abstract Syntax Viewer ***/",
"",
"#include <string>",
"#include \"Printer.H\"",
"#include \"Printer" ++hExt++ "\"",
"#define INDENT_WIDTH 2",
""
]
Expand Down Expand Up @@ -433,18 +433,18 @@ genPrintVisitorList (cat@(ListCat _), rules) = vcat
, ""
]
where
cl = identCat (normCat cat)
lty = text cl -- List type
itty = lty <> "::const_iterator" -- Iterator type
vname = text $ map toLower cl
prules = sortRulesByPrecedence rules
swRules f = switchByPrecedence "_i_" $
cl = identCat (normCat cat)
lty = text cl -- List type
itty = lty <> "::const_iterator" -- Iterator type
vname = text $ map toLower cl
prules = sortRulesByPrecedence rules
swRules f = switchByPrecedence "_i_" $
map (second $ sep . prListRule_) $
uniqOn fst $ filter f prules
-- Discard duplicates, can only handle one rule per precedence.
docs0 = swRules isNilFun
docs1 = swRules isOneFun
docs2 = swRules isConsFun
uniqOn fst $ filter f prules
-- Discard duplicates, can only handle one rule per precedence.
docs0 = swRules isNilFun
docs1 = swRules isOneFun
docs2 = swRules isConsFun

genPrintVisitorList _ = error "genPrintVisitorList expects a ListCat"

Expand Down
21 changes: 9 additions & 12 deletions source/src/BNFC/Backend/CPP/STL.hs
Original file line number Diff line number Diff line change
Expand Up @@ -48,10 +48,10 @@ makeCppStl opts cf = do
let (skelH, skelC) = cf2CVisitSkel True (inPackage opts) cf
mkCppFile ("Skeleton" ++ hExt) skelH
mkCppFile ("Skeleton" ++ cppExt) skelC
let (prinH, prinC) = cf2CPPPrinter True (inPackage opts) cf
let (prinH, prinC) = cf2CPPPrinter True (inPackage opts) cf hExt
mkCppFile ("Printer" ++ hExt) prinH
mkCppFile ("Printer" ++ cppExt) prinC
mkCppFile ("Test" ++ cppExt) (cpptest (inPackage opts) cf)
mkCppFile ("Test" ++ cppExt) (cpptest (inPackage opts) cf hExt)

case (ansi opts) of
BeyondAnsi -> do
Expand All @@ -75,10 +75,7 @@ makeCppStl opts cf = do
mkCppFileWithHint x = mkfile x commentWithEmacsModeHint
-- Switch C++ generator module
cppStdMode :: CppStdMode
cppStdMode = if Ansi == ansi opts then
CppStdAnsi (ansi opts)
else
CppStdBeyondAnsi (ansi opts)
cppStdMode = if Ansi == ansi opts then CppStdAnsi (ansi opts) else CppStdBeyondAnsi (ansi opts)
lexerExt = if Ansi == ansi opts then ".l" else ".ll"
parserExt = if Ansi == ansi opts then ".y" else ".yy"
cppExt = if Ansi == ansi opts then ".c" else ".cc"
Expand Down Expand Up @@ -113,18 +110,18 @@ printParseErrHeader inPackage =
, nsEnd inPackage
]

cpptest :: Maybe String -> CF -> String
cpptest inPackage cf = unlines $ concat
cpptest :: Maybe String -> CF -> String -> String
cpptest inPackage cf hExt = unlines $ concat
[ testfileHeader
, [ "",
"#include <cstdio>",
"#include <string>",
"#include <iostream>",
"#include <memory>",
"#include \"Parser.H\"",
"#include \"Printer.H\"",
"#include \"Absyn.H\"",
"#include \"ParserError.H\"",
"#include \"Parser" ++hExt++ "\"",
"#include \"Printer" ++hExt++ "\"",
"#include \"Absyn" ++hExt++ "\"",
"#include \"ParserError" ++hExt++ "\"",
"",
"void usage() {",
" printf(\"usage: Call with one of the following argument " ++
Expand Down
15 changes: 12 additions & 3 deletions source/src/BNFC/Backend/CPP/STL/CFtoSTLAbs.hs
Original file line number Diff line number Diff line change
Expand Up @@ -185,9 +185,8 @@ prCon mode (c,(f,cs)) =
CppStdBeyondAnsi _ -> unlines [
"class " ++f++ " : public " ++ c,
"{",
"private:",
unlines [" " ++ wrapUniquePtrIf isClass typ +++ var ++ ";" | (typ,isClass,var) <- cs],
"public:",
unlines [" " ++ wrapUniquePtrIf isClass typ +++ var ++ ";" | (typ,isClass,var) <- cs],
-- "right-hand side" operations; for move
" " ++ f ++ "(" ++ f ++ "&& rhs);",
" " ++ f ++ "& operator=(" ++ f ++ "&& rhs);",
Expand Down Expand Up @@ -230,7 +229,16 @@ prList mode (c, b) = case mode of {
"class " ++c++ " : public Visitable"
, "{"
, "public:"
, " std::vector<std::unique_ptr<" ++childClass++ ">>" +++ "list" ++ map toLower childClass ++ "_;"
, " std::vector<std::unique_ptr<" ++childClass++ ">>" +++ childClassVarName ++ ";"
, ""
-- ref: https://stackoverflow.com/questions/51148797/how-can-i-define-iterator-and-const-iterator-in-my-class-while-i-uses-stdvecto
, " // define iterator and const_iterator, expose it"
, " using iterator = typename std::vector<" ++childClass++ ">::iterator;"
, " using const_iterator = typename std::vector<" ++childClass++ ">::const_iterator;"
, " auto begin() const { return " ++childClassVarName++ ".begin(); }"
, " auto begin() { return " ++childClassVarName++ ".begin(); }"
, " auto end() const { return " ++childClassVarName++ ".end(); }"
, " auto end() { return " ++childClassVarName++ ".end(); }"
, ""
-- "right-hand side" operations; for move
, " " ++ c ++ "(" ++ c ++ "&& rhs);"
Expand All @@ -249,6 +257,7 @@ prList mode (c, b) = case mode of {
}
where
childClass = drop 4 c
childClassVarName = "list" ++ map toLower childClass ++ "_"
bas = applyWhen b (++ "*") $ drop 4 c {- drop "List" -}


Expand Down

0 comments on commit 6058374

Please sign in to comment.