{-# LANGUAGE NoImplicitPrelude #-}
module BNFC.Backend.Java.CFtoJLex15 ( cf2jlex ) where
import Prelude hiding ((<>))
import BNFC.CF
import BNFC.Backend.Common.NamedVariables
import BNFC.Backend.C.CFtoFlexC ( commentStates )
import BNFC.Backend.Java.RegToJLex
import BNFC.Options ( JavaLexerParser(..), RecordPositions(..) )
import BNFC.Utils ( cstring )
import Text.PrettyPrint
cf2jlex :: JavaLexerParser -> RecordPositions -> String -> CF -> (Doc, SymEnv)
cf2jlex :: JavaLexerParser -> RecordPositions -> String -> CF -> (Doc, SymEnv)
cf2jlex JavaLexerParser
jflex RecordPositions
rp String
packageBase CF
cf = (, SymEnv
env) (Doc -> (Doc, SymEnv)) -> ([Doc] -> Doc) -> [Doc] -> (Doc, SymEnv)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Doc] -> Doc
vcat ([Doc] -> (Doc, SymEnv)) -> [Doc] -> (Doc, SymEnv)
forall a b. (a -> b) -> a -> b
$
[ JavaLexerParser -> RecordPositions -> String -> Doc
prelude JavaLexerParser
jflex RecordPositions
rp String
packageBase
, CF -> Doc
cMacros CF
cf
, JavaLexerParser -> SymEnv -> Doc
lexSymbols JavaLexerParser
jflex SymEnv
env
, JavaLexerParser -> RecordPositions -> CF -> Doc
restOfJLex JavaLexerParser
jflex RecordPositions
rp CF
cf
]
where
env :: SymEnv
env = (String -> Int -> (String, String)) -> [String] -> [Int] -> SymEnv
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith (\ String
s Int
n -> (String
s, String
"_SYMB_" String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
n)) (CF -> [String]
forall function. CFG function -> [String]
cfgSymbols CF
cf [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ CF -> [String]
forall function. CFG function -> [String]
reservedWords CF
cf) [(Int
0 :: Int)..]
prelude :: JavaLexerParser -> RecordPositions -> String -> Doc
prelude :: JavaLexerParser -> RecordPositions -> String -> Doc
prelude JavaLexerParser
jflex RecordPositions
rp String
packageBase = [Doc] -> Doc
vcat
[ [Doc] -> Doc
hsep [ Doc
"// This", Doc
lexerName, Doc
"file was machine-generated by the BNF converter" ]
, Doc
"package" Doc -> Doc -> Doc
<+> String -> Doc
text String
packageBase Doc -> Doc -> Doc
<> Doc
";"
, Doc
""
, Doc
"import java_cup.runtime.*;"
, Doc
"%%"
, Doc
"%cup"
, Doc
"%unicode"
, (if RecordPositions
rp RecordPositions -> RecordPositions -> Bool
forall a. Eq a => a -> a -> Bool
== RecordPositions
RecordPositions
then [Doc] -> Doc
vcat
[ Doc
"%line"
, (if JavaLexerParser
jflex JavaLexerParser -> JavaLexerParser -> Bool
forall a. Eq a => a -> a -> Bool
== JavaLexerParser
JFlexCup then Doc
"%column" else Doc
"")
, Doc
"%char" ]
else Doc
"")
, Doc
"%public"
, Doc
"%{"
, Int -> Doc -> Doc
nest Int
2 (Doc -> Doc) -> Doc -> Doc
forall a b. (a -> b) -> a -> b
$ [Doc] -> Doc
vcat
[ Doc
"String pstring = new String();"
, Doc
"final int unknown = -1;"
, Doc
"ComplexSymbolFactory.Location left = new ComplexSymbolFactory.Location(unknown, unknown);"
, Doc
"ComplexSymbolFactory cf = new ComplexSymbolFactory();"
, Doc
"public SymbolFactory getSymbolFactory() { return cf; }"
, Doc
positionDeclarations
, Doc
"public int line_num() { return (yyline+1); }"
, Doc
"public ComplexSymbolFactory.Location left_loc() {"
, if RecordPositions
rp RecordPositions -> RecordPositions -> Bool
forall a. Eq a => a -> a -> Bool
== RecordPositions
RecordPositions
then Doc
" return new ComplexSymbolFactory.Location(yyline+1, yycolumn+1, yychar);"
else Doc
" return left;"
, Doc
"}"
, Doc
"public ComplexSymbolFactory.Location right_loc() {"
, Doc
" ComplexSymbolFactory.Location left = left_loc();"
, (if RecordPositions
rp RecordPositions -> RecordPositions -> Bool
forall a. Eq a => a -> a -> Bool
== RecordPositions
RecordPositions
then Doc
"return new ComplexSymbolFactory.Location(left.getLine(), left.getColumn()+yylength(), left.getOffset()+yylength());"
else Doc
"return left;")
, Doc
"}"
, Doc
"public String buff()" Doc -> Doc -> Doc
<+> Doc -> Doc
braces
(if JavaLexerParser
jflex JavaLexerParser -> JavaLexerParser -> Bool
forall a. Eq a => a -> a -> Bool
== JavaLexerParser
JFlexCup
then Doc
"return new String(zzBuffer,zzCurrentPos,10).trim();"
else Doc
"return new String(yy_buffer,yy_buffer_index,10).trim();")
]
, Doc
"%}"
, if JavaLexerParser
jflex JavaLexerParser -> JavaLexerParser -> Bool
forall a. Eq a => a -> a -> Bool
/= JavaLexerParser
JFlexCup then [Doc] -> Doc
vcat [Doc
"%eofval{"
, Doc
" return cf.newSymbol(\"EOF\", sym.EOF, left_loc(), left_loc());"
, Doc
"%eofval}"]
else Doc
""
]
where
lexerName :: Doc
lexerName = case JavaLexerParser
jflex of
JavaLexerParser
JFlexCup -> Doc
"JFlex"
JavaLexerParser
JLexCup -> Doc
"JLex"
JavaLexerParser
Antlr4 -> Doc
forall a. HasCallStack => a
undefined
positionDeclarations :: Doc
positionDeclarations
| JavaLexerParser
jflex JavaLexerParser -> JavaLexerParser -> Bool
forall a. Eq a => a -> a -> Bool
== JavaLexerParser
JFlexCup = Doc
""
| RecordPositions
rp RecordPositions -> RecordPositions -> Bool
forall a. Eq a => a -> a -> Bool
== RecordPositions
RecordPositions = Doc
"int yycolumn = unknown - 1;"
| Bool
otherwise = [Doc] -> Doc
vcat
[ Doc
"int yyline = unknown - 1;"
, Doc
"int yycolumn = unknown - 1;"
, Doc
"int yychar = unknown;"
]
cMacros :: CF -> Doc
cMacros :: CF -> Doc
cMacros CF
cf = [Doc] -> Doc
vcat ([Doc] -> Doc) -> [Doc] -> Doc
forall a b. (a -> b) -> a -> b
$ [[Doc]] -> [Doc]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
[ [ Doc
"LETTER = ({CAPITAL}|{SMALL})"
, Doc
"CAPITAL = [A-Z\\xC0-\\xD6\\xD8-\\xDE]"
, Doc
"SMALL = [a-z\\xDF-\\xF6\\xF8-\\xFF]"
, Doc
"DIGIT = [0-9]"
, Doc
"IDENT = ({LETTER}|{DIGIT}|['_])"
]
, (String -> Doc) -> [String] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map (String -> Doc
text (String -> Doc) -> (String -> String) -> String -> Doc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String
"%state " String -> String -> String
forall a. [a] -> [a] -> [a]
++)) ([String] -> [Doc]) -> [String] -> [Doc]
forall a b. (a -> b) -> a -> b
$ Int -> [String] -> [String]
forall a. Int -> [a] -> [a]
take (CF -> Int
numberOfBlockCommentForms CF
cf) [String]
commentStates
, [ Doc
"%state CHAR"
, Doc
"%state CHARESC"
, Doc
"%state CHAREND"
, Doc
"%state STRING"
, Doc
"%state ESCAPED"
, Doc
"%%"
]
]
lexSymbols :: JavaLexerParser -> SymEnv -> Doc
lexSymbols :: JavaLexerParser -> SymEnv -> Doc
lexSymbols JavaLexerParser
jflex SymEnv
ss = [Doc] -> Doc
vcat ([Doc] -> Doc) -> [Doc] -> Doc
forall a b. (a -> b) -> a -> b
$ ((String, String) -> Doc) -> SymEnv -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map (String, String) -> Doc
transSym SymEnv
ss
where
transSym :: (String, String) -> Doc
transSym (String
s,String
r) =
Doc
"<YYINITIAL>" Doc -> Doc -> Doc
<> String -> Doc
text (String -> String
escapeChars String
s) Doc -> Doc -> Doc
<> Doc
" { return cf.newSymbol(\"\", sym."
Doc -> Doc -> Doc
<> String -> Doc
text String
r Doc -> Doc -> Doc
<> Doc
", left_loc(), right_loc()); }"
escapeChars :: String -> String
escapeChars :: String -> String
escapeChars = (Char -> String) -> String -> String
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (JavaLexerParser -> Char -> String
escapeChar JavaLexerParser
jflex)
restOfJLex :: JavaLexerParser -> RecordPositions -> CF -> Doc
restOfJLex :: JavaLexerParser -> RecordPositions -> CF -> Doc
restOfJLex JavaLexerParser
jflex RecordPositions
rp CF
cf = [Doc] -> Doc
vcat
[ (SymEnv, [String]) -> Doc
lexComments (CF -> (SymEnv, [String])
comments CF
cf)
, Doc
""
, Doc
userDefTokens
, String -> Doc -> Doc
ifC String
catString Doc
strStates
, String -> Doc -> Doc
ifC String
catChar Doc
chStates
, String -> Doc -> Doc
ifC String
catDouble
Doc
"<YYINITIAL>{DIGIT}+\".\"{DIGIT}+(\"e\"(\\-)?{DIGIT}+)? { return cf.newSymbol(\"\", sym._DOUBLE_, left_loc(), right_loc(), new Double(yytext())); }"
, String -> Doc -> Doc
ifC String
catInteger
Doc
"<YYINITIAL>{DIGIT}+ { return cf.newSymbol(\"\", sym._INTEGER_, left_loc(), right_loc(), new Integer(yytext())); }"
, String -> Doc -> Doc
ifC String
catIdent
Doc
"<YYINITIAL>{LETTER}{IDENT}* { return cf.newSymbol(\"\", sym._IDENT_, left_loc(), right_loc(), yytext().intern()); }"
, Doc
"<YYINITIAL>[ \\t\\r\\n\\f] { /* ignore white space. */ }"
, if JavaLexerParser
jflex JavaLexerParser -> JavaLexerParser -> Bool
forall a. Eq a => a -> a -> Bool
== JavaLexerParser
JFlexCup
then Doc
"<<EOF>> { return cf.newSymbol(\"EOF\", sym.EOF, left_loc(), left_loc()); }"
else Doc
""
, if RecordPositions
rp RecordPositions -> RecordPositions -> Bool
forall a. Eq a => a -> a -> Bool
== RecordPositions
RecordPositions
then Doc
". { throw new Error(\"Illegal Character <\"+yytext()+\"> at \"+(yyline+1)" Doc -> Doc -> Doc
<>
(if JavaLexerParser
jflex JavaLexerParser -> JavaLexerParser -> Bool
forall a. Eq a => a -> a -> Bool
== JavaLexerParser
JFlexCup then Doc
"+\":\"+(yycolumn+1)+\"(\"+yychar+\")\"" else Doc
"") Doc -> Doc -> Doc
<> Doc
"); }"
else Doc
". { throw new Error(\"Illegal Character <\"+yytext()+\">\"); }"
]
where
ifC :: TokenCat -> Doc -> Doc
ifC :: String -> Doc -> Doc
ifC String
cat Doc
s = if CF -> Cat -> Bool
forall f. CFG f -> Cat -> Bool
isUsedCat CF
cf (String -> Cat
TokenCat String
cat) then Doc
s else Doc
""
userDefTokens :: Doc
userDefTokens = [Doc] -> Doc
vcat
[ Doc
"<YYINITIAL>" Doc -> Doc -> Doc
<> String -> Doc
text (JavaLexerParser -> Reg -> String
printRegJLex JavaLexerParser
jflex Reg
exp)
Doc -> Doc -> Doc
<+> Doc
"{ return cf.newSymbol(\"\", sym." Doc -> Doc -> Doc
<> String -> Doc
text String
name
Doc -> Doc -> Doc
<> Doc
", left_loc(), right_loc(), yytext().intern()); }"
| (String
name, Reg
exp) <- CF -> [(String, Reg)]
forall f. CFG f -> [(String, Reg)]
tokenPragmas CF
cf ]
strStates :: Doc
strStates = [Doc] -> Doc
vcat
[ Doc
"<YYINITIAL>\"\\\"\" { left = left_loc(); yybegin(STRING); }"
, Doc
"<STRING>\\\\ { yybegin(ESCAPED); }"
, Doc
"<STRING>\\\" { String foo = pstring; pstring = new String(); yybegin(YYINITIAL); return cf.newSymbol(\"\", sym._STRING_, left, right_loc(), foo.intern()); }"
, Doc
"<STRING>. { pstring += yytext(); }"
, Doc
"<STRING>\\r\\n|\\r|\\n { throw new Error(\"Unterminated string on line \" + left.getLine() " Doc -> Doc -> Doc
<>
(if JavaLexerParser
jflex JavaLexerParser -> JavaLexerParser -> Bool
forall a. Eq a => a -> a -> Bool
== JavaLexerParser
JFlexCup then Doc
"+ \" begining at column \" + left.getColumn()" else Doc
"") Doc -> Doc -> Doc
<> Doc
"); }"
, if JavaLexerParser
jflex JavaLexerParser -> JavaLexerParser -> Bool
forall a. Eq a => a -> a -> Bool
== JavaLexerParser
JFlexCup
then Doc
"<STRING><<EOF>> { throw new Error(\"Unterminated string at EOF, beginning at \" + left.getLine() + \":\" + left.getColumn()); }"
else Doc
""
, Doc
"<ESCAPED>n { pstring += \"\\n\"; yybegin(STRING); }"
, Doc
"<ESCAPED>t { pstring += \"\\t\"; yybegin(STRING); }"
, Doc
"<ESCAPED>r { pstring += \"\\r\"; yybegin(STRING); }"
, Doc
"<ESCAPED>f { pstring += \"\\f\"; yybegin(STRING); }"
, Doc
"<ESCAPED>\\\" { pstring += \"\\\"\"; yybegin(STRING); }"
, Doc
"<ESCAPED>\\\\ { pstring += \"\\\\\"; yybegin(STRING); }"
, Doc
"<ESCAPED>. { pstring += yytext(); yybegin(STRING); }"
, Doc
"<ESCAPED>\\r\\n|\\r|\\n { throw new Error(\"Unterminated string on line \" + left.getLine() " Doc -> Doc -> Doc
<>
(if JavaLexerParser
jflex JavaLexerParser -> JavaLexerParser -> Bool
forall a. Eq a => a -> a -> Bool
== JavaLexerParser
JFlexCup then Doc
"+ \" beginning at column \" + left.getColumn()" else Doc
"") Doc -> Doc -> Doc
<> Doc
"); }"
, if JavaLexerParser
jflex JavaLexerParser -> JavaLexerParser -> Bool
forall a. Eq a => a -> a -> Bool
== JavaLexerParser
JFlexCup
then Doc
"<ESCAPED><<EOF>> { throw new Error(\"Unterminated string at EOF, beginning at \" + left.getLine() + \":\" + left.getColumn()); }"
else Doc
""
]
chStates :: Doc
chStates = [Doc] -> Doc
vcat
[ Doc
"<YYINITIAL>\"'\" { left = left_loc(); yybegin(CHAR); }"
, Doc
"<CHAR>\\\\ { yybegin(CHARESC); }"
, Doc
"<CHAR>[^'] { yybegin(CHAREND); return cf.newSymbol(\"\", sym._CHAR_, left, right_loc(), new Character(yytext().charAt(0))); }"
, Doc
"<CHAR>\\r\\n|\\r|\\n { throw new Error(\"Unterminated character literal on line \" + left.getLine() " Doc -> Doc -> Doc
<>
(if JavaLexerParser
jflex JavaLexerParser -> JavaLexerParser -> Bool
forall a. Eq a => a -> a -> Bool
== JavaLexerParser
JFlexCup then Doc
"+ \" beginning at column \" + left.getColumn()" else Doc
"") Doc -> Doc -> Doc
<> Doc
"); }"
, if JavaLexerParser
jflex JavaLexerParser -> JavaLexerParser -> Bool
forall a. Eq a => a -> a -> Bool
== JavaLexerParser
JFlexCup
then Doc
"<CHAR><<EOF>> { throw new Error(\"Unterminated character literal at EOF, beginning at \" + left.getLine() + \":\" + left.getColumn()); }"
else Doc
""
, Doc
"<CHARESC>n { yybegin(CHAREND); return cf.newSymbol(\"\", sym._CHAR_, left, right_loc(), new Character('\\n')); }"
, Doc
"<CHARESC>t { yybegin(CHAREND); return cf.newSymbol(\"\", sym._CHAR_, left, right_loc(), new Character('\\t')); }"
, Doc
"<CHARESC>r { yybegin(CHAREND); return cf.newSymbol(\"\", sym._CHAR_, left, right_loc(), new Character('\\r')); }"
, Doc
"<CHARESC>f { yybegin(CHAREND); return cf.newSymbol(\"\", sym._CHAR_, left, right_loc(), new Character('\\f')); }"
, Doc
"<CHARESC>. { yybegin(CHAREND); return cf.newSymbol(\"\", sym._CHAR_, left, right_loc(), new Character(yytext().charAt(0))); }"
, Doc
"<CHARESC>\\r\\n|\\r|\\n { throw new Error(\"Unterminated character literal on line \" + left.getLine() " Doc -> Doc -> Doc
<>
(if JavaLexerParser
jflex JavaLexerParser -> JavaLexerParser -> Bool
forall a. Eq a => a -> a -> Bool
== JavaLexerParser
JFlexCup then Doc
"+ \" beginning at column \" + left.getColumn()" else Doc
"") Doc -> Doc -> Doc
<> Doc
"); }"
, if JavaLexerParser
jflex JavaLexerParser -> JavaLexerParser -> Bool
forall a. Eq a => a -> a -> Bool
== JavaLexerParser
JFlexCup
then Doc
"<CHARESC><<EOF>> { throw new Error(\"Unterminated character literal at EOF, beginning at \" + left.getLine() + \":\" + left.getColumn()); }"
else Doc
""
, Doc
"<CHAREND>\"'\" {yybegin(YYINITIAL);}"
, Doc
"<CHAREND>\\r\\n|\\r|\\n { throw new Error(\"Unterminated character literal on line \" + left.getLine() " Doc -> Doc -> Doc
<>
(if JavaLexerParser
jflex JavaLexerParser -> JavaLexerParser -> Bool
forall a. Eq a => a -> a -> Bool
== JavaLexerParser
JFlexCup then Doc
"+ \" beginning at column \" + left.getColumn()" else Doc
"") Doc -> Doc -> Doc
<> Doc
"); }"
, if JavaLexerParser
jflex JavaLexerParser -> JavaLexerParser -> Bool
forall a. Eq a => a -> a -> Bool
== JavaLexerParser
JFlexCup
then Doc
"<CHAREND><<EOF>> { throw new Error(\"Unterminated character literal at EOF, beginning at \" + left.getLine() + \":\" + left.getColumn()); }"
else Doc
""
]
lexComments :: ([(String, String)], [String]) -> Doc
(SymEnv
m,[String]
s) = [Doc] -> Doc
vcat ([Doc] -> Doc) -> [Doc] -> Doc
forall a b. (a -> b) -> a -> b
$ [[Doc]] -> [Doc]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
[ (String -> Doc) -> [String] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map String -> Doc
lexSingleComment [String]
s
, ((String, String) -> String -> Doc) -> SymEnv -> [String] -> [Doc]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith (String, String) -> String -> Doc
lexMultiComment SymEnv
m [String]
commentStates
]
lexSingleComment :: String -> Doc
String
c =
Doc
"<YYINITIAL>" Doc -> Doc -> Doc
<> String -> Doc
cstring String
c Doc -> Doc -> Doc
<> Doc
"[^\\n]* { /* skip */ }"
lexMultiComment :: (String, String) -> String -> Doc
(String
b,String
e) String
comment = [Doc] -> Doc
vcat
[ Doc
"<YYINITIAL>" Doc -> Doc -> Doc
<> String -> Doc
cstring String
b Doc -> Doc -> Doc
<+> Doc
"{ yybegin(" Doc -> Doc -> Doc
<> String -> Doc
text String
comment Doc -> Doc -> Doc
<> Doc
"); }"
, Doc
commentTag Doc -> Doc -> Doc
<> String -> Doc
cstring String
e Doc -> Doc -> Doc
<+> Doc
"{ yybegin(YYINITIAL); }"
, Doc
commentTag Doc -> Doc -> Doc
<> Doc
". { /* skip */ }"
, Doc
commentTag Doc -> Doc -> Doc
<> Doc
"[\\n] { /* skip */ }"
]
where
commentTag :: Doc
commentTag = String -> Doc
text (String -> Doc) -> String -> Doc
forall a b. (a -> b) -> a -> b
$ String
"<" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
comment String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
">"