{-
    BNF Converter: C++ Main file
    Copyright (C) 2004  Author:  Markus Forsberg, Michael Pellauer
-}

module BNFC.Backend.CPP.NoSTL (makeCppNoStl) 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.NoSTL.CFtoCPPAbs
import BNFC.Backend.CPP.STL.CFtoCVisitSkelSTL
import BNFC.Backend.CPP.PrettyPrinter
import qualified BNFC.Backend.Common.Makefile as Makefile

makeCppNoStl :: SharedOptions -> CF -> MkFiles ()
makeCppNoStl :: SharedOptions -> CF -> MkFiles ()
makeCppNoStl SharedOptions
opts CF
cf = do
    let ([Char]
hfile, [Char]
cfile) = [Char] -> CF -> ([Char], [Char])
cf2CPPAbs [Char]
name CF
cf
    [Char] -> [Char] -> MkFiles ()
forall {c}. FileContent c => [Char] -> c -> MkFiles ()
mkCppFile [Char]
"Absyn.H" [Char]
hfile
    [Char] -> [Char] -> MkFiles ()
forall {c}. FileContent c => [Char] -> c -> MkFiles ()
mkCppFile [Char]
"Absyn.C" [Char]
cfile
    [Char] -> [Char] -> MkFiles ()
forall {c}. FileContent c => [Char] -> c -> MkFiles ()
mkCppFile [Char]
"Buffer.H" [Char]
bufferH
    [Char] -> [Char] -> MkFiles ()
forall {c}. FileContent c => [Char] -> c -> MkFiles ()
mkCppFile [Char]
"Buffer.C" ([Char] -> MkFiles ()) -> [Char] -> MkFiles ()
forall a b. (a -> b) -> a -> b
$ [Char] -> [Char]
bufferC [Char]
"Buffer.H"
    let ([Char]
flex, SymMap
env) = ParserMode -> CF -> ([Char], SymMap)
cf2flex ParserMode
parserMode CF
cf
    [Char] -> [Char] -> MkFiles ()
forall {c}. FileContent c => [Char] -> c -> MkFiles ()
mkCppFileWithHint ([Char]
name [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
".l") [Char]
flex
    [Char] -> [Char] -> MkFiles ()
forall {c}. FileContent c => [Char] -> c -> MkFiles ()
mkCppFileWithHint ([Char]
name [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
".y") ([Char] -> MkFiles ()) -> [Char] -> MkFiles ()
forall a b. (a -> b) -> a -> b
$ RecordPositions -> ParserMode -> CF -> SymMap -> [Char]
cf2Bison (SharedOptions -> RecordPositions
linenumbers SharedOptions
opts) ParserMode
parserMode CF
cf SymMap
env
    [Char] -> [Char] -> MkFiles ()
forall {c}. FileContent c => [Char] -> c -> MkFiles ()
mkCppFile [Char]
"Parser.H" ([Char] -> MkFiles ()) -> [Char] -> MkFiles ()
forall a b. (a -> b) -> a -> b
$
      [Cat] -> [Char]
mkHeaderFile (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)
    let ([Char]
skelH, [Char]
skelC) = Bool -> Maybe [Char] -> CF -> ([Char], [Char])
cf2CVisitSkel Bool
False Maybe [Char]
forall a. Maybe a
Nothing CF
cf
    [Char] -> [Char] -> MkFiles ()
forall {c}. FileContent c => [Char] -> c -> MkFiles ()
mkCppFile [Char]
"Skeleton.H" [Char]
skelH
    [Char] -> [Char] -> MkFiles ()
forall {c}. FileContent c => [Char] -> c -> MkFiles ()
mkCppFile [Char]
"Skeleton.C" [Char]
skelC
    let ([Char]
prinH, [Char]
prinC) = Bool -> Maybe [Char] -> CF -> ([Char], [Char])
cf2CPPPrinter Bool
False Maybe [Char]
forall a. Maybe a
Nothing CF
cf
    [Char] -> [Char] -> MkFiles ()
forall {c}. FileContent c => [Char] -> c -> MkFiles ()
mkCppFile [Char]
"Printer.H" [Char]
prinH
    [Char] -> [Char] -> MkFiles ()
forall {c}. FileContent c => [Char] -> c -> MkFiles ()
mkCppFile [Char]
"Printer.C" [Char]
prinC
    [Char] -> [Char] -> MkFiles ()
forall {c}. FileContent c => [Char] -> c -> MkFiles ()
mkCppFile [Char]
"Test.C" (CF -> [Char]
cpptest CF
cf)
    SharedOptions -> ([Char] -> Doc) -> MkFiles ()
Makefile.mkMakefile SharedOptions
opts (([Char] -> Doc) -> MkFiles ()) -> ([Char] -> Doc) -> MkFiles ()
forall a b. (a -> b) -> a -> b
$ [Char] -> [Char] -> [Char] -> Doc
makefile [Char]
prefix [Char]
name
  where
    name :: String
    name :: [Char]
name = SharedOptions -> [Char]
lang SharedOptions
opts
    -- The prefix is a string used by flex and bison
    -- that is prepended to generated function names.
    -- It should be a valid C identifier.
    prefix :: String
    prefix :: [Char]
prefix = [Char] -> [Char]
snakeCase_ [Char]
name [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"_"
    parserMode :: ParserMode
    parserMode :: ParserMode
parserMode = Bool -> [Char] -> ParserMode
CParser Bool
True [Char]
prefix
    mkCppFile :: [Char] -> c -> MkFiles ()
mkCppFile         [Char]
x = [Char] -> ([Char] -> [Char]) -> c -> MkFiles ()
forall c.
FileContent c =>
[Char] -> ([Char] -> [Char]) -> c -> MkFiles ()
mkfile [Char]
x [Char] -> [Char]
comment
    mkCppFileWithHint :: [Char] -> c -> MkFiles ()
mkCppFileWithHint [Char]
x = [Char] -> ([Char] -> [Char]) -> c -> MkFiles ()
forall c.
FileContent c =>
[Char] -> ([Char] -> [Char]) -> c -> MkFiles ()
mkfile [Char]
x [Char] -> [Char]
commentWithEmacsModeHint

cpptest :: CF -> String
cpptest :: CF -> [Char]
cpptest CF
cf = [[Char]] -> [Char]
unlines ([[Char]] -> [Char]) -> [[Char]] -> [Char]
forall a b. (a -> b) -> a -> b
$ [[[Char]]] -> [[Char]]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
  [ [[Char]]
testfileHeader
  , [ [Char]
"",
    [Char]
"#include <stdio.h>",
    [Char]
"#include <string.h>",
    [Char]
"#include \"Parser.H\"",
    [Char]
"#include \"Printer.H\"",
    [Char]
"#include \"Absyn.H\"",
    [Char]
"",
    [Char]
"void usage() {",
    [Char]
"  printf(\"usage: Call with one of the following argument " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++
      [Char]
"combinations:\\n\");",
    [Char]
"  printf(\"\\t--help\\t\\tDisplay this help message.\\n\");",
    [Char]
"  printf(\"\\t(no arguments)\\tParse stdin verbosely.\\n\");",
    [Char]
"  printf(\"\\t(files)\\t\\tParse content of files verbosely.\\n\");",
    [Char]
"  printf(\"\\t-s (files)\\tSilent mode. Parse content of files " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++
      [Char]
"silently.\\n\");",
    [Char]
"}",
    [Char]
"",
    [Char]
"int main(int argc, char ** argv)",
    [Char]
"{",
    [Char]
"  FILE *input;",
    [Char]
"  int quiet = 0;",
    [Char]
"  char *filename = NULL;",
    [Char]
"",
    [Char]
"  if (argc > 1) {",
    [Char]
"    if (strcmp(argv[1], \"-s\") == 0) {",
    [Char]
"      quiet = 1;",
    [Char]
"      if (argc > 2) {",
    [Char]
"        filename = argv[2];",
    [Char]
"      } else {",
    [Char]
"        input = stdin;",
    [Char]
"      }",
    [Char]
"    } else {",
    [Char]
"      filename = argv[1];",
    [Char]
"    }",
    [Char]
"  }",
    [Char]
"",
    [Char]
"  if (filename) {",
    [Char]
"    input = fopen(filename, \"r\");",
    [Char]
"    if (!input) {",
    [Char]
"      usage();",
    [Char]
"      exit(1);",
    [Char]
"    }",
    [Char]
"  } else input = stdin;",
    [Char]
"  /* The default entry point is used. For other options see Parser.H */",
    [Char]
"  " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
dat [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" *parse_tree = p" [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
def [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"(input);",
    [Char]
"  if (parse_tree)",
    [Char]
"  {",
    [Char]
"    printf(\"\\nParse Successful!\\n\");",
    [Char]
"    if (!quiet) {",
    [Char]
"      printf(\"\\n[Abstract Syntax]\\n\");",
    [Char]
"      ShowAbsyn *s = new ShowAbsyn();",
    [Char]
"      printf(\"%s\\n\\n\", s->show(parse_tree));",
    [Char]
"      printf(\"[Linearized Tree]\\n\");",
    [Char]
"      PrintAbsyn *p = new PrintAbsyn();",
    [Char]
"      printf(\"%s\\n\\n\", p->print(parse_tree));",
    [Char]
"    }",
    [Char]
"    delete(parse_tree);",
    [Char]
"    return 0;",
    [Char]
"  }",
    [Char]
"  return 1;",
    [Char]
"}",
    [Char]
""
    ]
  ]
  where
   cat :: Cat
cat = CF -> Cat
firstEntry CF
cf
   dat :: [Char]
dat = Cat -> [Char]
identCat (Cat -> [Char]) -> Cat -> [Char]
forall a b. (a -> b) -> a -> b
$ Cat -> Cat
normCat Cat
cat
   def :: [Char]
def = Cat -> [Char]
identCat Cat
cat

mkHeaderFile :: [Cat] -> String
mkHeaderFile :: [Cat] -> [Char]
mkHeaderFile [Cat]
eps = [[Char]] -> [Char]
unlines ([[Char]] -> [Char]) -> [[Char]] -> [Char]
forall a b. (a -> b) -> a -> b
$ [[[Char]]] -> [[Char]]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
  [ [ [Char]
"#ifndef PARSER_HEADER_FILE"
    , [Char]
"#define PARSER_HEADER_FILE"
    , [Char]
""
    , [Char]
"#include <stdio.h>"
    , [Char]
"#include \"Absyn.H\""
    , [Char]
""
    ]
  , (Cat -> [Char]) -> [Cat] -> [[Char]]
forall a b. (a -> b) -> [a] -> [b]
map Cat -> [Char]
mkFunc [Cat]
eps
  , [ [Char]
""
    , [Char]
"#endif"
    ]
  ]
  where
  mkFunc :: Cat -> [Char]
mkFunc Cat
s = Cat -> [Char]
identCat (Cat -> Cat
normCat Cat
s) [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"*" [Char] -> [Char] -> [Char]
+++ [Char]
"p" [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ Cat -> [Char]
identCat Cat
s [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"(FILE *inp);"