module BNFC.Backend.CPP.STL (makeCppStl,) where
import Data.Foldable (toList)
import BNFC.Utils
import BNFC.CF
import BNFC.Options
import BNFC.Backend.Base
import BNFC.Backend.C ( bufferH, bufferC, comment, testfileHeader )
import BNFC.Backend.C.CFtoBisonC ( cf2Bison )
import BNFC.Backend.C.CFtoFlexC ( cf2flex, ParserMode(..) )
import BNFC.Backend.CPP.Common ( commentWithEmacsModeHint )
import BNFC.Backend.CPP.Makefile
import BNFC.Backend.CPP.STL.CFtoSTLAbs
import BNFC.Backend.CPP.STL.CFtoCVisitSkelSTL
import BNFC.Backend.CPP.PrettyPrinter
import BNFC.Backend.CPP.STL.STLUtils
import qualified BNFC.Backend.Common.Makefile as Makefile
makeCppStl :: SharedOptions -> CF -> MkFiles ()
makeCppStl :: SharedOptions -> CF -> MkFiles ()
makeCppStl SharedOptions
opts CF
cf = do
let (String
hfile, String
cfile) = RecordPositions -> Maybe String -> String -> CF -> (String, String)
cf2CPPAbs (SharedOptions -> RecordPositions
linenumbers SharedOptions
opts) (SharedOptions -> Maybe String
inPackage SharedOptions
opts) String
name CF
cf
String -> String -> MkFiles ()
forall c. FileContent c => String -> c -> MkFiles ()
mkCppFile String
"Absyn.H" String
hfile
String -> String -> MkFiles ()
forall c. FileContent c => String -> c -> MkFiles ()
mkCppFile String
"Absyn.C" String
cfile
String -> String -> MkFiles ()
forall c. FileContent c => String -> c -> MkFiles ()
mkCppFile String
"Buffer.H" String
bufferH
String -> String -> MkFiles ()
forall c. FileContent c => String -> c -> MkFiles ()
mkCppFile String
"Buffer.C" (String -> MkFiles ()) -> String -> MkFiles ()
forall a b. (a -> b) -> a -> b
$ String -> String
bufferC String
"Buffer.H"
let (String
flex, SymMap
env) = ParserMode -> CF -> (String, SymMap)
cf2flex ParserMode
parserMode CF
cf
String -> String -> MkFiles ()
forall c. FileContent c => String -> c -> MkFiles ()
mkCppFileWithHint (String
name String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
".l") String
flex
String -> String -> MkFiles ()
forall c. FileContent c => String -> c -> MkFiles ()
mkCppFileWithHint (String
name String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
".y") (String -> MkFiles ()) -> String -> MkFiles ()
forall a b. (a -> b) -> a -> b
$ RecordPositions -> ParserMode -> CF -> SymMap -> String
cf2Bison (SharedOptions -> RecordPositions
linenumbers SharedOptions
opts) ParserMode
parserMode CF
cf SymMap
env
String -> String -> MkFiles ()
forall c. FileContent c => String -> c -> MkFiles ()
mkCppFile String
"Parser.H" (String -> MkFiles ()) -> String -> MkFiles ()
forall a b. (a -> b) -> a -> b
$
Maybe String -> [Cat] -> String
mkHeaderFile (SharedOptions -> Maybe String
inPackage SharedOptions
opts) (NonEmpty Cat -> [Cat]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList (NonEmpty Cat -> [Cat]) -> NonEmpty Cat -> [Cat]
forall a b. (a -> b) -> a -> b
$ CF -> NonEmpty Cat
forall f. CFG f -> NonEmpty Cat
allEntryPoints CF
cf)
String -> String -> MkFiles ()
forall c. FileContent c => String -> c -> MkFiles ()
mkCppFile String
"ParserError.H" (String -> MkFiles ()) -> String -> MkFiles ()
forall a b. (a -> b) -> a -> b
$ Maybe String -> String
printParseErrHeader (SharedOptions -> Maybe String
inPackage SharedOptions
opts)
let (String
skelH, String
skelC) = Bool -> Maybe String -> CF -> (String, String)
cf2CVisitSkel Bool
True (SharedOptions -> Maybe String
inPackage SharedOptions
opts) CF
cf
String -> String -> MkFiles ()
forall c. FileContent c => String -> c -> MkFiles ()
mkCppFile String
"Skeleton.H" String
skelH
String -> String -> MkFiles ()
forall c. FileContent c => String -> c -> MkFiles ()
mkCppFile String
"Skeleton.C" String
skelC
let (String
prinH, String
prinC) = Bool -> Maybe String -> CF -> (String, String)
cf2CPPPrinter Bool
True (SharedOptions -> Maybe String
inPackage SharedOptions
opts) CF
cf
String -> String -> MkFiles ()
forall c. FileContent c => String -> c -> MkFiles ()
mkCppFile String
"Printer.H" String
prinH
String -> String -> MkFiles ()
forall c. FileContent c => String -> c -> MkFiles ()
mkCppFile String
"Printer.C" String
prinC
String -> String -> MkFiles ()
forall c. FileContent c => String -> c -> MkFiles ()
mkCppFile String
"Test.C" (Maybe String -> CF -> String
cpptest (SharedOptions -> Maybe String
inPackage SharedOptions
opts) CF
cf)
SharedOptions -> (String -> Doc) -> MkFiles ()
Makefile.mkMakefile SharedOptions
opts ((String -> Doc) -> MkFiles ()) -> (String -> Doc) -> MkFiles ()
forall a b. (a -> b) -> a -> b
$ String -> String -> String -> Doc
makefile String
prefix String
name
where
name :: String
name :: String
name = SharedOptions -> String
lang SharedOptions
opts
prefix :: String
prefix :: String
prefix = String -> String
snakeCase_ String
name String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"_"
parserMode :: ParserMode
parserMode :: ParserMode
parserMode = Maybe String -> String -> ParserMode
CppParser (SharedOptions -> Maybe String
inPackage SharedOptions
opts) String
prefix
mkCppFile :: String -> c -> MkFiles ()
mkCppFile String
x = String -> (String -> String) -> c -> MkFiles ()
forall c.
FileContent c =>
String -> (String -> String) -> c -> MkFiles ()
mkfile String
x String -> String
comment
mkCppFileWithHint :: String -> c -> MkFiles ()
mkCppFileWithHint String
x = String -> (String -> String) -> c -> MkFiles ()
forall c.
FileContent c =>
String -> (String -> String) -> c -> MkFiles ()
mkfile String
x String -> String
commentWithEmacsModeHint
printParseErrHeader :: Maybe String -> String
Maybe String
inPackage =
[String] -> String
unlines
[
String
" #pragma once "
, String
" #include <string>"
, String
" #include <stdexcept>"
, String
""
, Maybe String -> String
nsStart Maybe String
inPackage
, String
" class parse_error : public std::runtime_error"
, String
" {"
, String
" public:"
, String
" parse_error(int line, std::string str)"
, String
" : std::runtime_error(str)"
, String
" , m_line(line) {}"
, String
" int getLine() {"
, String
" return m_line;"
, String
" } "
, String
" private:"
, String
" int m_line;"
, String
" }; "
, Maybe String -> String
nsEnd Maybe String
inPackage
]
cpptest :: Maybe String -> CF -> String
cpptest :: Maybe String -> CF -> String
cpptest Maybe String
inPackage CF
cf = [String] -> String
unlines ([String] -> String) -> [String] -> String
forall a b. (a -> b) -> a -> b
$ [[String]] -> [String]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
[ [String]
testfileHeader
, [ String
"",
String
"#include <cstdio>",
String
"#include <string>",
String
"#include <iostream>",
String
"#include \"Parser.H\"",
String
"#include \"Printer.H\"",
String
"#include \"Absyn.H\"",
String
"#include \"ParserError.H\"",
String
"",
String
"void usage() {",
String
" printf(\"usage: Call with one of the following argument " String -> String -> String
forall a. [a] -> [a] -> [a]
++
String
"combinations:\\n\");",
String
" printf(\"\\t--help\\t\\tDisplay this help message.\\n\");",
String
" printf(\"\\t(no arguments)\\tParse stdin verbosely.\\n\");",
String
" printf(\"\\t(files)\\t\\tParse content of files verbosely.\\n\");",
String
" printf(\"\\t-s (files)\\tSilent mode. Parse content of files " String -> String -> String
forall a. [a] -> [a] -> [a]
++
String
"silently.\\n\");",
String
"}",
String
"",
String
"int main(int argc, char ** argv)",
String
"{",
String
" FILE *input;",
String
" int quiet = 0;",
String
" char *filename = NULL;",
String
"",
String
" if (argc > 1) {",
String
" if (strcmp(argv[1], \"-s\") == 0) {",
String
" quiet = 1;",
String
" if (argc > 2) {",
String
" filename = argv[2];",
String
" } else {",
String
" input = stdin;",
String
" }",
String
" } else {",
String
" filename = argv[1];",
String
" }",
String
" }",
String
"",
String
" if (filename) {",
String
" input = fopen(filename, \"r\");",
String
" if (!input) {",
String
" usage();",
String
" exit(1);",
String
" }",
String
" } else input = stdin;",
String
" /* The default entry point is used. For other options see Parser.H */",
String
" " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
scope String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
dat String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" *parse_tree = NULL;",
String
" try { ",
String
" parse_tree = " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
scope String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"p" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
def String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"(input);",
String
" } catch( " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
scope String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"parse_error &e) {",
String
" std::cerr << \"Parse error on line \" << e.getLine() << \"\\n\"; ",
String
" }",
String
" if (parse_tree)",
String
" {",
String
" printf(\"\\nParse Successful!\\n\");",
String
" if (!quiet) {",
String
" printf(\"\\n[Abstract Syntax]\\n\");",
String
" " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
scope String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"ShowAbsyn *s = new " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
scope String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"ShowAbsyn();",
String
" printf(\"%s\\n\\n\", s->show(parse_tree));",
String
" printf(\"[Linearized Tree]\\n\");",
String
" " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
scope String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"PrintAbsyn *p = new " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
scope String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"PrintAbsyn();",
String
" printf(\"%s\\n\\n\", p->print(parse_tree));",
String
" }",
String
" delete(parse_tree);",
String
" return 0;",
String
" }",
String
" return 1;",
String
"}",
String
""
]
]
where
cat :: Cat
cat = CF -> Cat
firstEntry CF
cf
dat :: String
dat = Cat -> String
identCat (Cat -> String) -> Cat -> String
forall a b. (a -> b) -> a -> b
$ Cat -> Cat
normCat Cat
cat
def :: String
def = Cat -> String
identCat Cat
cat
scope :: String
scope = Maybe String -> String
nsScope Maybe String
inPackage
mkHeaderFile :: Maybe String -> [Cat] -> String
Maybe String
inPackage [Cat]
eps = [String] -> String
unlines ([String] -> String) -> [String] -> String
forall a b. (a -> b) -> a -> b
$ [[String]] -> [String]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
[ [ String
"#ifndef " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
hdef
, String
"#define " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
hdef
, String
""
, String
"#include<vector>"
, String
"#include<string>"
, String
"#include<cstdio>"
, String
"#include \"Absyn.H\""
, String
""
, Maybe String -> String
nsStart Maybe String
inPackage
]
, (Cat -> [String]) -> [Cat] -> [String]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap Cat -> [String]
mkFuncs [Cat]
eps
, [ Maybe String -> String
nsEnd Maybe String
inPackage
, String
""
, String
"#endif"
]
]
where
hdef :: String
hdef = Maybe String -> String -> String
nsDefine Maybe String
inPackage String
"PARSER_HEADER_FILE"
mkFuncs :: Cat -> [String]
mkFuncs Cat
s =
[ Cat -> String
identCat (Cat -> Cat
normCat Cat
s) String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"*" String -> String -> String
+++ String
"p" String -> String -> String
forall a. [a] -> [a] -> [a]
++ Cat -> String
identCat Cat
s String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"(FILE *inp);"
, Cat -> String
identCat (Cat -> Cat
normCat Cat
s) String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"*" String -> String -> String
+++ String
"p" String -> String -> String
forall a. [a] -> [a] -> [a]
++ Cat -> String
identCat Cat
s String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"(const char *str);"
]