{-# LANGUAGE LambdaCase #-}

{-
    BNF Converter: Latex Generator
    Copyright (C) 2004  Author:  Markus Forsberg, Aarne Ranta

-}

module BNFC.Backend.Latex where

import qualified Data.List as List
import System.FilePath ((<.>),replaceExtension)
import Text.Printf

import BNFC.Abs (Reg (..))
import BNFC.Options hiding (Backend)
import BNFC.Backend.Base
import BNFC.Backend.Common.Makefile as Makefile
import BNFC.CF
import BNFC.Utils
import BNFC.PrettyPrint hiding (empty)

-- | Entry point: create .tex file and a Makefile to compile it.
makeLatex :: SharedOptions -> CF -> Backend
makeLatex :: SharedOptions -> CF -> Backend
makeLatex SharedOptions
opts CF
cf = do
    let texfile :: FilePath
texfile = FilePath
name FilePath -> FilePath -> FilePath
<.> FilePath
"tex"
    FilePath -> FilePath -> Backend
forall c. FileContent c => FilePath -> c -> Backend
mkfile FilePath
texfile (FilePath -> CF -> FilePath
cfToLatex FilePath
name CF
cf)
    SharedOptions -> (FilePath -> Doc) -> Backend
Makefile.mkMakefile SharedOptions
opts (FilePath -> FilePath -> Doc
makefile FilePath
texfile)
  where name :: FilePath
name = SharedOptions -> FilePath
lang SharedOptions
opts

-- | Create a makefile for the given tex file
--
-- >>> makefile "myFile.tex" "Makefile"
-- all : myFile.pdf
-- <BLANKLINE>
-- myFile.pdf : myFile.tex
-- 	pdflatex myFile.tex
-- <BLANKLINE>
-- clean :
-- 	-rm myFile.pdf myFile.aux myFile.log
-- <BLANKLINE>
-- cleanall : clean
-- 	-rm Makefile myFile.tex
-- <BLANKLINE>
--
makefile :: String -> String -> Doc
makefile :: FilePath -> FilePath -> Doc
makefile FilePath
texfile FilePath
basename = [Doc] -> Doc
vcat
    [ FilePath -> [FilePath] -> [FilePath] -> Doc
Makefile.mkRule FilePath
"all" [FilePath
pdffile]
        []
    , FilePath -> [FilePath] -> [FilePath] -> Doc
Makefile.mkRule FilePath
pdffile [FilePath
texfile]
        [ FilePath -> FilePath -> FilePath
forall r. PrintfType r => FilePath -> r
printf FilePath
"pdflatex %s" FilePath
texfile ]
    , FilePath -> [FilePath] -> [FilePath] -> Doc
Makefile.mkRule FilePath
"clean" []
        [ [FilePath] -> FilePath
unwords [ FilePath
"-rm", FilePath
pdffile, FilePath
auxfile, FilePath
logfile ]]
    , FilePath -> [FilePath] -> [FilePath] -> Doc
Makefile.mkRule FilePath
"cleanall" [FilePath
"clean"]
        [ [FilePath] -> FilePath
unwords [ FilePath
"-rm", FilePath
basename, FilePath
texfile ]]
    ]
  where pdffile :: FilePath
pdffile = FilePath -> FilePath -> FilePath
replaceExtension FilePath
texfile FilePath
"pdf"
        auxfile :: FilePath
auxfile = FilePath -> FilePath -> FilePath
replaceExtension FilePath
texfile FilePath
"aux"
        logfile :: FilePath
logfile = FilePath -> FilePath -> FilePath
replaceExtension FilePath
texfile FilePath
"log"

-- | Create content of .tex file.
cfToLatex :: String -> CF -> String
cfToLatex :: FilePath -> CF -> FilePath
cfToLatex FilePath
name CF
cf = [FilePath] -> FilePath
unlines
  -- Overall structure of created LaTeX document:
  [ FilePath
"\\batchmode"
  , FilePath -> FilePath
beginDocument FilePath
name
  , FilePath
macros
  , FilePath
introduction
  , FilePath -> CF -> FilePath
prtTerminals FilePath
name CF
cf
  , FilePath -> CF -> FilePath
prtBNF FilePath
name CF
cf
  , FilePath
endDocument
  ]

introduction :: String
introduction :: FilePath
introduction = [FilePath] -> FilePath
unlines
  [ FilePath
"This document was automatically generated by the {\\em BNF-Converter}."
  , FilePath
"It was generated together with the lexer, the parser, and the"
  , FilePath
"abstract syntax module, which guarantees that the document"
  , FilePath
"matches with the implementation of the language"
  , FilePath
"(provided no hand-hacking has taken place)."
  ]

prtTerminals :: String -> CF -> String
prtTerminals :: FilePath -> CF -> FilePath
prtTerminals FilePath
name CF
cf = [FilePath] -> FilePath
unlines ([FilePath] -> FilePath) -> [FilePath] -> FilePath
forall a b. (a -> b) -> a -> b
$
  [ FilePath
"\\section*{The lexical structure of " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
name FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"}"
  , FilePath
""
  ] [FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++ CF -> [FilePath]
identSection CF
cf [FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++
  [ FilePath
"\\subsection*{Literals}"
  , FilePath -> CF -> FilePath
prtLiterals FilePath
name CF
cf
  ] [FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++ ((FilePath, Reg) -> FilePath) -> [(FilePath, Reg)] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
map (FilePath, Reg) -> FilePath
prtOwnToken (CF -> [(FilePath, Reg)]
forall f. CFG f -> [(FilePath, Reg)]
tokenPragmas CF
cf) [FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++
  [ FilePath
"\\subsection*{Reserved words and symbols}"
  , FilePath -> CF -> FilePath
prtReserved FilePath
name CF
cf
  , FilePath -> CF -> FilePath
prtSymb FilePath
name CF
cf
  , FilePath
"\\subsection*{Comments}"
  , ([(FilePath, FilePath)], [FilePath]) -> FilePath
prtComments (([(FilePath, FilePath)], [FilePath]) -> FilePath)
-> ([(FilePath, FilePath)], [FilePath]) -> FilePath
forall a b. (a -> b) -> a -> b
$ CF -> ([(FilePath, FilePath)], [FilePath])
comments CF
cf
  ]

identSection :: CF -> [String]
identSection :: CF -> [FilePath]
identSection CF
cf
  | CF -> Bool
forall f. CFG f -> Bool
hasIdent CF
cf = [ FilePath
"\\subsection*{Identifiers}" ] [FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++ [FilePath]
prtIdentifiers
  | Bool
otherwise   = []

prtIdentifiers :: [String]
prtIdentifiers :: [FilePath]
prtIdentifiers =
  [ FilePath
"Identifiers \\nonterminal{Ident} are unquoted strings beginning with a letter,"
  , FilePath
"followed by any combination of letters, digits, and the characters {\\tt \\_ '},"
  , FilePath
"reserved words excluded."
  ]

prtLiterals :: String -> CF -> String
prtLiterals :: FilePath -> CF -> FilePath
prtLiterals FilePath
_ CF
cf =
  [FilePath] -> FilePath
unlines ([FilePath] -> FilePath)
-> ([FilePath] -> [FilePath]) -> [FilePath] -> FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[FilePath]] -> [FilePath]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([[FilePath]] -> [FilePath])
-> ([FilePath] -> [[FilePath]]) -> [FilePath] -> [FilePath]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [FilePath] -> [[FilePath]] -> [[FilePath]]
forall a. a -> [a] -> [a]
List.intersperse [FilePath
""] ([[FilePath]] -> [[FilePath]])
-> ([FilePath] -> [[FilePath]]) -> [FilePath] -> [[FilePath]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (FilePath -> [FilePath]) -> [FilePath] -> [[FilePath]]
forall a b. (a -> b) -> [a] -> [b]
map FilePath -> [FilePath]
stringLit ([FilePath] -> [[FilePath]])
-> ([FilePath] -> [FilePath]) -> [FilePath] -> [[FilePath]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (FilePath -> Bool) -> [FilePath] -> [FilePath]
forall a. (a -> Bool) -> [a] -> [a]
filter (FilePath -> FilePath -> Bool
forall a. Eq a => a -> a -> Bool
/= FilePath
catIdent) ([FilePath] -> FilePath) -> [FilePath] -> FilePath
forall a b. (a -> b) -> a -> b
$ CF -> [FilePath]
forall f. CFG f -> [FilePath]
literals CF
cf

stringLit :: TokenCat -> [String]
stringLit :: FilePath -> [FilePath]
stringLit = \case
  FilePath
"Char" ->
    [ FilePath
"Character literals \\nonterminal{Char}\\ have the form"
    , FilePath
"\\terminal{'}$c$\\terminal{'}, where $c$ is any single character."
    ]
  FilePath
"String" ->
    [ FilePath
"String literals \\nonterminal{String}\\ have the form"
    , FilePath
"\\terminal{\"}$x$\\terminal{\"}, where $x$ is any sequence of any characters"
    , FilePath
"except \\terminal{\"}\\ unless preceded by \\verb6\\6."
    ]
  FilePath
"Integer" ->
    [ FilePath
"Integer literals \\nonterminal{Int}\\ are nonempty sequences of digits."
    ]
  FilePath
"Double" ->
    [ FilePath
"Double-precision float literals \\nonterminal{Double}\\ have the structure"
    , FilePath
"indicated by the regular expression" FilePath -> FilePath -> FilePath
+++
      FilePath
"$\\nonterminal{digit}+ \\mbox{{\\it `.'}} \\nonterminal{digit}+ (\\mbox{{\\it `e'}} \\mbox{{\\it `-'}}? \\nonterminal{digit}+)?$ i.e.\\"
    , FilePath
"two sequences of digits separated by a decimal point, optionally"
    , FilePath
"followed by an unsigned or negative exponent."
    ]
  FilePath
_ -> []

prtOwnToken :: (FilePath, Reg) -> FilePath
prtOwnToken (FilePath
name,Reg
reg) = [FilePath] -> FilePath
unlines
  [ FilePath
name FilePath -> FilePath -> FilePath
+++ FilePath
"literals are recognized by the regular expression",
   FilePath
"\\(" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++
   Reg -> FilePath
latexRegExp Reg
reg FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++
   FilePath
"\\)"
  ]

prtComments :: ([(String,String)],[String]) -> String
prtComments :: ([(FilePath, FilePath)], [FilePath]) -> FilePath
prtComments ([(FilePath, FilePath)]
xs,[FilePath]
ys) =
    (if [FilePath] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [FilePath]
ys
        then FilePath
"There are no single-line comments in the grammar. \\\\"
        else FilePath
"Single-line comments begin with " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
sing FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++FilePath
". \\\\")
    FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++
    (if [(FilePath, FilePath)] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [(FilePath, FilePath)]
xs
        then FilePath
"There are no multiple-line comments in the grammar."
        else FilePath
"Multiple-line comments are  enclosed with " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
mult FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++FilePath
".")
 where
 sing :: FilePath
sing = FilePath -> [FilePath] -> FilePath
forall a. [a] -> [[a]] -> [a]
List.intercalate FilePath
", " ([FilePath] -> FilePath) -> [FilePath] -> FilePath
forall a b. (a -> b) -> a -> b
$ (FilePath -> FilePath) -> [FilePath] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
map (FilePath -> FilePath
symbol(FilePath -> FilePath)
-> (FilePath -> FilePath) -> FilePath -> FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
.FilePath -> FilePath
prt) [FilePath]
ys
 mult :: FilePath
mult = FilePath -> [FilePath] -> FilePath
forall a. [a] -> [[a]] -> [a]
List.intercalate FilePath
", " ([FilePath] -> FilePath) -> [FilePath] -> FilePath
forall a b. (a -> b) -> a -> b
$
         ((FilePath, FilePath) -> FilePath)
-> [(FilePath, FilePath)] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
map (\(FilePath
x,FilePath
y) -> FilePath -> FilePath
symbol (FilePath -> FilePath
prt FilePath
x)
                       FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
" and " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++
                      FilePath -> FilePath
symbol (FilePath -> FilePath
prt FilePath
y)) [(FilePath, FilePath)]
xs

prtSymb :: String -> CF -> String
prtSymb :: FilePath -> CF -> FilePath
prtSymb FilePath
name CF
cf = case CF -> [FilePath]
forall f. CFG f -> [FilePath]
cfgSymbols CF
cf of
                   [] -> FilePath
"\nThere are no symbols in " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
name FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
".\\\\\n"
                   [FilePath]
xs -> FilePath
"The symbols used in " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
name FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
" are the following: \\\\\n"
                         FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++
                         Int -> [[FilePath]] -> FilePath
tabular Int
3 ([FilePath] -> [[FilePath]]
forall a. Monoid a => [a] -> [[a]]
three ([FilePath] -> [[FilePath]]) -> [FilePath] -> [[FilePath]]
forall a b. (a -> b) -> a -> b
$ (FilePath -> FilePath) -> [FilePath] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
map (FilePath -> FilePath
symbol(FilePath -> FilePath)
-> (FilePath -> FilePath) -> FilePath -> FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
.FilePath -> FilePath
prt) [FilePath]
xs)

prtReserved :: String -> CF -> String
prtReserved :: FilePath -> CF -> FilePath
prtReserved FilePath
name CF
cf = case CF -> [FilePath]
forall f. CFG f -> [FilePath]
reservedWords CF
cf of
                       [] -> FilePath -> FilePath
stringRes FilePath
name FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++
                             FilePath
"\nThere are no reserved words in " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
name FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
".\\\\\n"
                       [FilePath]
xs -> FilePath -> FilePath
stringRes FilePath
name FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++
                             Int -> [[FilePath]] -> FilePath
tabular Int
3 ([FilePath] -> [[FilePath]]
forall a. Monoid a => [a] -> [[a]]
three ([FilePath] -> [[FilePath]]) -> [FilePath] -> [[FilePath]]
forall a b. (a -> b) -> a -> b
$ (FilePath -> FilePath) -> [FilePath] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
map (FilePath -> FilePath
reserved(FilePath -> FilePath)
-> (FilePath -> FilePath) -> FilePath -> FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
.FilePath -> FilePath
prt) [FilePath]
xs)

stringRes :: String -> String
stringRes :: FilePath -> FilePath
stringRes FilePath
name = [FilePath] -> FilePath
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
                 [FilePath
"The set of reserved words is the set of terminals ",
                  FilePath
"appearing in the grammar. Those reserved words ",
                  FilePath
"that consist of non-letter characters are called symbols, and ",
                  FilePath
"they are treated in a different way from those that ",
                  FilePath
"are similar to identifiers. The lexer ",
                  FilePath
"follows rules familiar from languages ",
                  FilePath
"like Haskell, C, and Java, including longest match ",
                  FilePath
"and spacing conventions.",
                  FilePath
"\n\n",
                  FilePath
"The reserved words used in " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
name FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
" are the following: \\\\\n"]

-- | Group a list into blocks of 3 elements.
three :: Monoid a => [a] -> [[a]]
three :: [a] -> [[a]]
three []         = []
three [a
x]        = [[a
x,a
forall a. Monoid a => a
mempty,a
forall a. Monoid a => a
mempty]]
three [a
x,a
y]      = [[a
x,a
y,a
forall a. Monoid a => a
mempty]]
three (a
x:a
y:a
z:[a]
xs) = [a
x,a
y,a
z] [a] -> [[a]] -> [[a]]
forall a. a -> [a] -> [a]
: [a] -> [[a]]
forall a. Monoid a => [a] -> [[a]]
three [a]
xs

prtBNF :: String -> CF -> String
prtBNF :: FilePath -> CF -> FilePath
prtBNF FilePath
name CF
cf = [FilePath] -> FilePath
unlines
  [ FilePath
"\\section*{The syntactic structure of " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
name FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"}"
  , FilePath
""
  , FilePath
"Non-terminals are enclosed between $\\langle$ and $\\rangle$."
  , FilePath
"The symbols " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
arrow FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
" (production), " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
delimiter FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
" (union)"
  , FilePath
"and " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
empty FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
" (empty rule) belong to the BNF notation."
  , FilePath
"All other symbols are terminals.\\\\"
  , [(Cat, [Rule])] -> FilePath
prtRules (CF -> [(Cat, [Rule])]
ruleGroups CF
cf)
  ]

prtRules :: [(Cat,[Rule])] -> String
prtRules :: [(Cat, [Rule])] -> FilePath
prtRules          [] = []
prtRules ((Cat
c,[]):[(Cat, [Rule])]
xs)
    = Int -> [[FilePath]] -> FilePath
tabular Int
3 [[Cat -> FilePath
nonterminal Cat
c,FilePath
arrow,[]]] FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ [(Cat, [Rule])] -> FilePath
prtRules [(Cat, [Rule])]
xs
prtRules ((Cat
c, Rule
r : [Rule]
rs) : [(Cat, [Rule])]
xs)
    = Int -> [[FilePath]] -> FilePath
tabular Int
3 ([Cat -> FilePath
nonterminal Cat
c,FilePath
arrow,[Either Cat FilePath] -> FilePath
prtSymbols ([Either Cat FilePath] -> FilePath)
-> [Either Cat FilePath] -> FilePath
forall a b. (a -> b) -> a -> b
$ Rule -> [Either Cat FilePath]
forall function. Rul function -> [Either Cat FilePath]
rhsRule Rule
r] [FilePath] -> [[FilePath]] -> [[FilePath]]
forall a. a -> [a] -> [a]
:
                 [[[],FilePath
delimiter,[Either Cat FilePath] -> FilePath
prtSymbols (Rule -> [Either Cat FilePath]
forall function. Rul function -> [Either Cat FilePath]
rhsRule Rule
y)] | Rule
y <-  [Rule]
rs]) FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++
      [(Cat, [Rule])] -> FilePath
prtRules [(Cat, [Rule])]
xs

prtSymbols :: [Either Cat String] -> String
prtSymbols :: [Either Cat FilePath] -> FilePath
prtSymbols [] = FilePath
empty
prtSymbols [Either Cat FilePath]
xs = (Either Cat FilePath -> FilePath -> FilePath)
-> FilePath -> [Either Cat FilePath] -> FilePath
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr (FilePath -> FilePath -> FilePath
(+++) (FilePath -> FilePath -> FilePath)
-> (Either Cat FilePath -> FilePath)
-> Either Cat FilePath
-> FilePath
-> FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Either Cat FilePath -> FilePath
p) [] [Either Cat FilePath]
xs
 where p :: Either Cat FilePath -> FilePath
p (Left  Cat
r) = Cat -> FilePath
nonterminal Cat
r --- (prt r)
       p (Right FilePath
r) = FilePath -> FilePath
terminal    (FilePath -> FilePath
prt FilePath
r)


prt :: String -> String
prt :: FilePath -> FilePath
prt = (Char -> FilePath) -> FilePath -> FilePath
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap Char -> FilePath
escape
  where escape :: Char -> FilePath
escape Char
'\\'                               = FilePath
"$\\backslash$"
        escape Char
'~'                                = FilePath
"\\~{}"
        escape Char
'^'                                = FilePath
"{\\textasciicircum}"
        escape Char
c | Char
c Char -> FilePath -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` (FilePath
"$&%#_{}" :: String) = [Char
'\\', Char
c]
        escape Char
c | Char
c Char -> FilePath -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` (FilePath
"+=|<>-" :: String)  = FilePath
"{$"  FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ [Char
c] FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"$}"
        escape Char
c                                  = [Char
c]

macros :: String
macros :: FilePath
macros = [FilePath] -> FilePath
unlines
  [ FilePath
"\\newcommand{\\emptyP}{\\mbox{$\\epsilon$}}"
  , FilePath
"\\newcommand{\\terminal}[1]{\\mbox{{\\texttt {#1}}}}"
  , FilePath
"\\newcommand{\\nonterminal}[1]{\\mbox{$\\langle \\mbox{{\\sl #1 }} \\! \\rangle$}}"
  , FilePath
"\\newcommand{\\arrow}{\\mbox{::=}}"
  , FilePath
"\\newcommand{\\delimit}{\\mbox{$|$}}"
  , FilePath
"\\newcommand{\\reserved}[1]{\\mbox{{\\texttt {#1}}}}"
  , FilePath
"\\newcommand{\\literal}[1]{\\mbox{{\\texttt {#1}}}}"
  , FilePath
"\\newcommand{\\symb}[1]{\\mbox{{\\texttt {#1}}}}"
  ]

reserved :: String -> String
reserved :: FilePath -> FilePath
reserved FilePath
s = FilePath
"{\\reserved{" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
s FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"}}"

literal :: String -> String
literal :: FilePath -> FilePath
literal FilePath
s = FilePath
"{\\literal{" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
s FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"}}"

empty :: String
empty :: FilePath
empty = FilePath
"{\\emptyP}"

symbol :: String -> String
symbol :: FilePath -> FilePath
symbol FilePath
s = FilePath
"{\\symb{" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
s FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"}}"

tabular :: Int -> [[String]] -> String
tabular :: Int -> [[FilePath]] -> FilePath
tabular Int
n [[FilePath]]
xs = FilePath
"\n\\begin{tabular}{" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ [FilePath] -> FilePath
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat (Int -> FilePath -> [FilePath]
forall a. Int -> a -> [a]
replicate Int
n FilePath
"l") FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"}\n" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++
               ([FilePath] -> FilePath) -> [[FilePath]] -> FilePath
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (\(FilePath
a:[FilePath]
as) -> (FilePath -> FilePath -> FilePath)
-> FilePath -> [FilePath] -> FilePath
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr FilePath -> FilePath -> FilePath
(+++) FilePath
"\\\\\n" (FilePath
aFilePath -> [FilePath] -> [FilePath]
forall a. a -> [a] -> [a]
: (FilePath -> FilePath) -> [FilePath] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
map (Char
'&'Char -> FilePath -> FilePath
forall a. a -> [a] -> [a]
:) [FilePath]
as)) [[FilePath]]
xs FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++
               FilePath
"\\end{tabular}\\\\\n"

terminal :: String -> String
terminal :: FilePath -> FilePath
terminal FilePath
s = FilePath
"{\\terminal{" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
s FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"}}"

nonterminal :: Cat -> String
nonterminal :: Cat -> FilePath
nonterminal Cat
s = FilePath
"{\\nonterminal{" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath -> FilePath
mkId (Cat -> FilePath
identCat Cat
s) FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"}}" where
 mkId :: FilePath -> FilePath
mkId = (Char -> Char) -> FilePath -> FilePath
forall a b. (a -> b) -> [a] -> [b]
map Char -> Char
mk
 mk :: Char -> Char
mk Char
c = case Char
c of
   Char
'_' -> Char
'-' ---
   Char
_ -> Char
c


arrow :: String
arrow :: FilePath
arrow = FilePath
" {\\arrow} "

delimiter :: String
delimiter :: FilePath
delimiter = FilePath
" {\\delimit} "

beginDocument :: String -> String
beginDocument :: FilePath -> FilePath
beginDocument FilePath
name = [FilePath] -> FilePath
unlines
 [ FilePath
"%This Latex file is machine-generated by the BNF-converter"
 , FilePath
""
 , FilePath
"\\documentclass[a4paper,11pt]{article}"
 , FilePath
"\\usepackage[T1]{fontenc}"
 , FilePath
"\\usepackage[utf8x]{inputenc}"
 , FilePath
"\\setlength{\\parindent}{0mm}"
 , FilePath
"\\setlength{\\parskip}{1mm}"
 , FilePath
""
 , FilePath
"\\title{The Language " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
name FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"}"
 , FilePath
"\\author{BNF-converter}"
 , FilePath
""
 , FilePath
"\\begin{document}"
 , FilePath
"\\maketitle"
 , FilePath
""
 ]

endDocument :: String
endDocument :: FilePath
endDocument = [FilePath] -> FilePath
unlines
  [ FilePath
""
  , FilePath
"\\end{document}"
  ]

latexRegExp :: Reg -> String
latexRegExp :: Reg -> FilePath
latexRegExp = Int -> Reg -> FilePath
rex Int
0
  where
  rex :: Int -> Reg -> String
  rex :: Int -> Reg -> FilePath
rex Int
i = \case
    RSeq Reg
r0 Reg
r   -> Int -> Int -> FilePath -> FilePath
forall a. Ord a => a -> a -> FilePath -> FilePath
ifPar Int
i Int
2 (FilePath -> FilePath) -> FilePath -> FilePath
forall a b. (a -> b) -> a -> b
$ Int -> Reg -> FilePath
rex Int
2 Reg
r0 FilePath -> FilePath -> FilePath
+++ Int -> Reg -> FilePath
rex Int
2 Reg
r
    RAlt Reg
r0 Reg
r   -> Int -> Int -> FilePath -> FilePath
forall a. Ord a => a -> a -> FilePath -> FilePath
ifPar Int
i Int
1 (FilePath -> FilePath) -> FilePath -> FilePath
forall a b. (a -> b) -> a -> b
$ Int -> Reg -> FilePath
rex Int
1 Reg
r0 FilePath -> FilePath -> FilePath
+++ FilePath
"\\mid" FilePath -> FilePath -> FilePath
+++ Int -> Reg -> FilePath
rex Int
1 Reg
r
    RMinus Reg
r0 Reg
r -> Int -> Int -> FilePath -> FilePath
forall a. Ord a => a -> a -> FilePath -> FilePath
ifPar Int
i Int
1 (FilePath -> FilePath) -> FilePath -> FilePath
forall a b. (a -> b) -> a -> b
$ Int -> Reg -> FilePath
rex Int
2 Reg
r0 FilePath -> FilePath -> FilePath
+++ FilePath
"-" FilePath -> FilePath -> FilePath
+++ Int -> Reg -> FilePath
rex Int
2 Reg
r
    RStar Reg
r     -> Int -> Reg -> FilePath
rex Int
3 Reg
r FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"*"
    RPlus Reg
r     -> Int -> Reg -> FilePath
rex Int
3 Reg
r FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"+"
    ROpt Reg
r      -> Int -> Reg -> FilePath
rex Int
3 Reg
r FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"?"
    Reg
REps        -> FilePath
"\\epsilon"
    RChar Char
c     -> FilePath
"\\mbox{`" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath -> FilePath
prt [Char
c] FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"'}"
    RAlts FilePath
s     -> FilePath
"[" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"\\mbox{``" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath -> FilePath
prt FilePath
s FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"''}" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"]"
    RSeqs FilePath
s     -> FilePath
"\\{" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"\\mbox{``" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath -> FilePath
prt FilePath
s FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"''}" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"\\}"
    Reg
RDigit      -> FilePath
"{\\nonterminal{digit}}"
    Reg
RLetter     -> FilePath
"{\\nonterminal{letter}}"
    Reg
RUpper      -> FilePath
"{\\nonterminal{upper}}"
    Reg
RLower      -> FilePath
"{\\nonterminal{lower}}"
    Reg
RAny        -> FilePath
"{\\nonterminal{anychar}}"
  ifPar :: a -> a -> FilePath -> FilePath
ifPar a
i a
j FilePath
s = if a
i a -> a -> Bool
forall a. Ord a => a -> a -> Bool
> a
j then FilePath
"(" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
s FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
")" else FilePath
s