Skip to content
Open
Show file tree
Hide file tree
Changes from all commits
Commits
Show all changes
90 commits
Select commit Hold shift + click to select a range
7eff429
[ANTLR4] added generation for ANTLR4 files without target-specific co…
linkstaple Oct 3, 2023
8fa226c
[ANTLR4] erased rule labels for start rules
linkstaple Oct 8, 2023
aee84f2
[ANTLRv4] added generation of Makefile for ANTLR backend and several …
linkstaple Oct 9, 2023
ac40bf2
[ANTLRv4] some refactoring of antlr files
linkstaple Oct 9, 2023
1473ec2
[ANTLRv4] changes for antlr Makefile generation
linkstaple Oct 9, 2023
b0c0c40
[ANTLRv4] created new function for parsing ANTLR CLI options
linkstaple Oct 9, 2023
0c5c47a
[ANTLRv4] added support for -Xlog ANTLR flag
linkstaple Oct 9, 2023
f14b890
[ANTLRv4] -Xlog flag added to BNFC.Options
linkstaple Oct 9, 2023
6b13f6f
[ANTLRv4] added support for -listener and -no-visitor ANTLR flags
linkstaple Oct 9, 2023
f5809ea
[ANTLRv4] added support for -XdbgST ANTLR flag
linkstaple Oct 9, 2023
1cdfcd3
[ANTLRv4] fixed description for -listener and -visitor ANTLR options
linkstaple Oct 9, 2023
ef3056a
[ANTLRv4] added support for -XdbgSTWait ANTLR flag
linkstaple Oct 10, 2023
baf1186
[ANTLRv4] added support for -atn ANTLR flag
linkstaple Oct 10, 2023
6a3b6c6
[ANTLRv4] minor formatting fix
linkstaple Oct 10, 2023
066f725
[ANTLRv4] added support for ANTLR options of type 'name value'
linkstaple Oct 10, 2023
413f351
[ANTLRv4] added option for passing string with ANTLR options directly…
linkstaple Oct 10, 2023
d51337c
[ANTLRv4] update description for ANTLR output
linkstaple Oct 10, 2023
d34f4b2
[ANTLRv4] Makefile LANG variable is set to be equal package name
linkstaple Oct 11, 2023
38ff8fb
[ANTLRv4] stylistic changes
linkstaple Oct 16, 2023
cf895ce
[ANTLRv4] permanent camel case for .g4 files
linkstaple Oct 16, 2023
a914279
[ANTLRv4] Some improvements for Makefile gen
linkstaple Oct 19, 2023
1c6074f
added AST for Dart
xdkomel Oct 29, 2023
95cba43
[ANTLRv4] remove unworking code
linkstaple Nov 6, 2023
f9f696d
Merge branch 'master' into bnfc-antlr
linkstaple Nov 6, 2023
1636c9e
added an AST builder from the ANTLR parser
xdkomel Nov 6, 2023
7929533
Merge pull request #1 from linkstaple/bnfc-antlr
xdkomel Nov 22, 2023
57ddbc3
fix ast, remove the custom parser generator
xdkomel Nov 22, 2023
b95bbbb
merge with add-antlr-backend
xdkomel Nov 22, 2023
d72f4ba
make builder use extensions, match arguments in the g4
xdkomel Nov 23, 2023
a55d2e2
use functions instead of extensions, resolve common issues, leaving o…
xdkomel Nov 27, 2023
40b47fe
builder 85% done
xdkomel Dec 4, 2023
1f8aee7
added pretty printer first draft
xdkomel Dec 11, 2023
2358676
fixed show methods collisions
xdkomel Dec 11, 2023
df4f1b2
fixed different precedence printers
xdkomel Dec 11, 2023
091f72b
[ANTLRv4] expose antlrRuleLabel
linkstaple Dec 6, 2023
82e3385
[ANTLRv4] expose function for making left-recursive rules
linkstaple Dec 16, 2023
0d0c282
[ANTLRv4] resolve name collision for coercion types for ANTLR rule la…
linkstaple Dec 16, 2023
7e51440
a bit reorganized
xdkomel Jan 30, 2024
5b0ae7e
Merge pull request #2 from linkstaple/bnfc-antlr
xdkomel Jan 30, 2024
bb3c9c8
Merge branch 'master' of github.com:xdkomel/bnfc-dart into addDartBui…
xdkomel Jan 30, 2024
6d8d93b
Merge branch 'addPrettyPrinter' of github.com:xdkomel/bnfc-dart into …
xdkomel Jan 30, 2024
7a0148b
support coercion number
xdkomel Jan 30, 2024
45f6e26
Merge pull request #3 from xdkomel/addDartBuilder
xdkomel Jan 30, 2024
af36017
pretty printer w/o coercions & lists
xdkomel Jan 30, 2024
45c86d8
added sep&term, bug w/ coercions
xdkomel Feb 12, 2024
fa14c03
add precedence to the list printers
xdkomel Feb 18, 2024
af8f9ed
Merge pull request #4 from xdkomel/pretty-printer-sep-term
xdkomel Feb 18, 2024
3629ec0
finish mvp
xdkomel Feb 21, 2024
f5b436a
Merge pull request #5 from xdkomel/add-lists-builders
xdkomel Feb 21, 2024
c11d327
add skeleton generator & use Iterable where possible
xdkomel May 1, 2024
e4d5c96
generate project structure, undone
xdkomel May 2, 2024
98898ce
add skeleton and makefile
xdkomel May 2, 2024
77ad7e2
add naming and diretory options to antlr
xdkomel May 21, 2024
0c6be6d
Merge pull request #1 from xdkomel/bnfc-antlr
linkstaple May 26, 2024
02b3365
Merge branch 'master' into bnfc-antlr
linkstaple Jun 2, 2024
558deec
add project structure and makefile
xdkomel Jun 2, 2024
ce57565
Merge pull request #6 from xdkomel/add-skeleton
xdkomel Jun 2, 2024
aa88214
Merge branch 'master' into bnfc-antlr
xdkomel Jun 2, 2024
3901f5a
Merge pull request #7 from xdkomel/bnfc-antlr
xdkomel Jun 2, 2024
2899ef0
fix bug when merged
xdkomel Jun 2, 2024
6359382
fix builder and PP naming issues
xdkomel Jun 2, 2024
5dfd109
[ANTLRv4]: change label generation function to funName
linkstaple Jun 5, 2024
c00d058
Merge branch 'bnfc-antlr' of https://github.com/linkstaple/bnfc-ts-ex…
xdkomel Jun 8, 2024
f6fcda2
mostly adequate version
xdkomel Sep 1, 2024
28fed69
add: CLI Swift option
NAD777 Sep 1, 2024
21498bf
Add: AST and Make file generation for Swift
NAD777 Sep 1, 2024
18b748a
add first steps in builder, change generation structure, minor change…
NAD777 Sep 2, 2024
5cb52d9
Add: wrappers for build in Swift types
NAD777 Sep 3, 2024
0add675
fix: builder (no parant for empty assosiated values list), ast (wrap …
NAD777 Sep 3, 2024
fbde94c
refactoring: clean up and refactoring
NAD777 Sep 3, 2024
7b07752
refactoring: clean up make file, entry point for swift
NAD777 Sep 4, 2024
8a03a24
Move to lib generation instead of just files, improve generated files…
NAD777 Oct 20, 2024
2de0de0
Add public api, fix builder generation, fix package file generation a…
NAD777 Oct 20, 2024
59f0c55
Create files for skeleton, connect to Swift's part of BNFC
NAD777 Dec 15, 2024
521583b
Add first iteration of Skeleton generation, small fixes
NAD777 Jan 11, 2025
e6dfed3
feat(AST): refactoring, make properties public in wrappers for basic …
NAD777 Jan 15, 2025
9564801
feat(pretty-printer, builder): add first iteration of pretty-printer,…
NAD777 Jan 16, 2025
b975107
feat(pretty-printer): fix swift type-checker problem, delete protocol…
NAD777 Jan 23, 2025
596a556
feat(pretty-printer): adjust render according to stella, fix problem …
NAD777 Jan 23, 2025
5378262
Merge pull request #1 from NAD777/dev
NAD777 Jan 25, 2025
b566c39
feat(utils): adjust keywords and build ins
NAD777 Apr 6, 2025
547e637
Merge pull request #3 from NAD777/adjust-keywords
NAD777 Apr 6, 2025
d781af2
Merge pull request #4 from NAD777/dev
NAD777 Apr 6, 2025
197bf4e
feat(skeleton): change skeleton file dir
NAD777 Apr 27, 2025
b0e6f0a
Merge pull request #5 from NAD777/change-dir-of-skeleton-file
NAD777 Apr 27, 2025
553ff43
feat(builder, ast): change filenames according to swift conventions
NAD777 Apr 27, 2025
95841b1
Merge pull request #6 from NAD777/change-filename-of-ast-and-builder
NAD777 Apr 27, 2025
876ca2d
feat(skeleton): fix name collisions, user-defined types
NAD777 May 11, 2025
a2cf53c
feat(all, skeleton): make lower first case letter, try to fix skeleton
NAD777 Jun 23, 2025
a02d025
feat(public-api): change ast provider function name
NAD777 Jun 23, 2025
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
50 changes: 50 additions & 0 deletions .vscode/tasks.json
Original file line number Diff line number Diff line change
@@ -0,0 +1,50 @@

{
// Automatically created by phoityne-vscode extension.

"version": "2.0.0",
"presentation": {
"reveal": "always",
"panel": "new"
},
"tasks": [
{
// F7
"group": {
"kind": "build",
"isDefault": true
},
"label": "haskell build",
"type": "shell",
//"command": "cabal configure && cabal build"
"command": "stack build"
},
{
// F6
"group": "build",
"type": "shell",
"label": "haskell clean & build",
//"command": "cabal clean && cabal configure && cabal build"
"command": "stack clean && stack build"
//"command": "stack clean ; stack build" // for powershell
},
{
// F8
"group": {
"kind": "test",
"isDefault": true
},
"type": "shell",
"label": "haskell test",
//"command": "cabal test"
"command": "stack test"
},
{
// F6
"isBackground": true,
"type": "shell",
"label": "haskell watch",
"command": "stack build --test --no-run-tests --file-watch"
}
]
}
23 changes: 23 additions & 0 deletions source/BNFC.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -264,6 +264,29 @@ library
BNFC.Backend.Java.RegToAntlrLexer
BNFC.Backend.Java.Utils

-- Dart backend
BNFC.Backend.Dart
BNFC.Backend.Dart.CFtoDartAST
BNFC.Backend.Dart.CFtoDartBuilder
BNFC.Backend.Dart.Common
BNFC.Backend.Dart.CFtoDartPrinter
BNFC.Backend.Dart.CFtoDartSkeleton

-- Swift backend
BNFC.Backend.Swift
BNFC.Backend.Swift.CFtoSwiftAST
BNFC.Backend.Swift.CFtoSwiftBuilder
BNFC.Backend.Swift.Common
BNFC.Backend.Swift.CFtoSwiftPrinter
BNFC.Backend.Swift.CFtoSwiftSkeleton

-- Antlr4 backend
BNFC.Backend.Antlr
BNFC.Backend.Antlr.CFtoAntlr4Lexer
BNFC.Backend.Antlr.CFtoAntlr4Parser
BNFC.Backend.Antlr.RegToAntlrLexer
BNFC.Backend.Antlr.Utils

-- XML backend
BNFC.Backend.XML

Expand Down
6 changes: 6 additions & 0 deletions source/main/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -25,6 +25,9 @@ import BNFC.Backend.Java
import BNFC.Backend.Latex
import BNFC.Backend.OCaml
import BNFC.Backend.Pygments
import BNFC.Backend.Dart (makeDart)
import BNFC.Backend.Swift (makeSwift)
import BNFC.Backend.Antlr
import BNFC.Backend.TreeSitter
import BNFC.CF (CF)
import BNFC.GetCF
Expand Down Expand Up @@ -81,5 +84,8 @@ maketarget = \case
TargetJava -> makeJava
TargetOCaml -> makeOCaml
TargetPygments -> makePygments
TargetDart -> makeDart
TargetSwift -> makeSwift
TargetAntlr -> makeAntlr
TargetCheck -> error "impossible"
TargetTreeSitter -> makeTreeSitter
101 changes: 101 additions & 0 deletions source/src/BNFC/Backend/Antlr.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,101 @@
{-# LANGUAGE RecordWildCards #-}

module BNFC.Backend.Antlr ( makeAntlr, makeAntlr', DirectoryOptions(..) ) where

import Prelude hiding ((<>))
import System.FilePath ((</>), pathSeparator, (<.>))
import Text.PrettyPrint.HughesPJ (vcat)
import Data.Maybe (fromMaybe)

import BNFC.Utils
( NameStyle(CamelCase),
mkName,
replace,
(+.+),
(+++) )
import BNFC.CF
import BNFC.Options as Options
import BNFC.Backend.Base
import BNFC.Backend.Antlr.CFtoAntlr4Lexer
import BNFC.Backend.Antlr.CFtoAntlr4Parser
import BNFC.Backend.Antlr.Utils (dotG4, getAntlrOptions)
import BNFC.Backend.Common.Makefile as MakeFile
( mkMakefile, mkVar, mkRule, refVar )

data DirectoryOptions = DirectoryOptions
{ baseDirectory :: Maybe String
, nameStyle :: Maybe NameStyle }

makeAntlr :: SharedOptions -> CF -> MkFiles ()
makeAntlr opts cf = makeAntlr' opts cf DirectoryOptions {
baseDirectory=Nothing
, nameStyle=Nothing }

makeAntlr' :: SharedOptions -> CF -> DirectoryOptions -> MkFiles ()
makeAntlr' opts@Options{..} cf DirectoryOptions{..} = do
let packageBase = maybe id (+.+) inPackage pkg
dirBase = fromMaybe (pkgToDir packageBase) baseDirectory

let lexerName = mkFilename "Lexer"
lexerFile = dotG4 lexerName
(lex, env) = cf2AntlrLex lexerName cf
-- Where the lexer file is created. lex is the content!
mkfile (dirBase </> lexerFile) mkAntlrComment lex

let parserName = mkFilename "Parser"
parserFile = dotG4 parserName
parserContent = cf2AntlrParse lexerName parserName cf linenumbers env
mkfile (dirBase </> parserFile) mkAntlrComment parserContent

MakeFile.mkMakefile optMake makefileContent
where
pkg = mkName [] (fromMaybe CamelCase nameStyle) lang
pkgToDir = replace '.' pathSeparator
mkFilename ending = mkName [] (fromMaybe CamelCase nameStyle) (pkg ++ ending)

makeVars x = [MakeFile.mkVar n v | (n,v) <- x]
makeRules x = [MakeFile.mkRule tar dep recipe | (tar, dep, recipe) <- x]

langRef = MakeFile.refVar "LANG"

lexerVarName = "LEXER_GRAMMAR_FILENAME"
lexerGrammarFile = (langRef </>) . dotG4 $ langRef ++ "Lexer"

parserVarName = "PARSER_GRAMMAR_FILENAME"
parserGrammarFile = (langRef </>) . dotG4 $ langRef ++ "Parser"

makefileVars = vcat $ makeVars
[ ("LANG", pkg)
, (lexerVarName, lexerGrammarFile)
, (parserVarName, parserGrammarFile)
, ("ANTLR4", "java org.antlr.v4.Tool")
, ("ANTLR_OPTIONS", getAntlrOptions opts)
, ("DIRECT_OPTIONS", antlrOpts)
]

genAntlrRecipe = ((MakeFile.refVar "ANTLR4" +++ MakeFile.refVar "ANTLR_OPTIONS" +++ MakeFile.refVar "DIRECT_OPTIONS") +++) . MakeFile.refVar

antlrFiles =
let ns = fromMaybe CamelCase nameStyle
in map (langRef </>)
[ mkName [] ns (pkg +++ "Lexer") <.> "interp"
, mkName [] ns (pkg +++ "Parser") <.> "interp"
, mkName [] ns (pkg +++ "Lexer") <.> "tokens"
, mkName [] ns (pkg +++ "Parser") <.> "tokens"
]

makefileRules = vcat $ makeRules
[ (".PHONY", ["all", "clean-antlr", "remove"], [])
, ("all", [langRef], [])
, ("lexer", [MakeFile.refVar lexerVarName], [genAntlrRecipe lexerVarName])
, ("parser", [MakeFile.refVar parserVarName], [genAntlrRecipe parserVarName])
, (langRef, ["lexer", "parser"], [])
, ("clean-antlr", [],
map ("rm -f" +++) antlrFiles )
, ("remove", [], ["rm -rf" +++ langRef])
]

makefileContent _ = vcat [makefileVars, "", makefileRules]

mkAntlrComment :: String -> String
mkAntlrComment = ("// ANTLRv4 " ++)
173 changes: 173 additions & 0 deletions source/src/BNFC/Backend/Antlr/CFtoAntlr4Lexer.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,173 @@
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}

{-
BNF Converter: Java Antlr4 Lexer generator
Copyright (C) 2015 Author: Gabriele Paganelli

Description : This module generates the Antlr4 input file.
Based on CFtoJLex15.hs

Author : Gabriele Paganelli ([email protected])
Created : 15 Oct, 2015

-}

module BNFC.Backend.Antlr.CFtoAntlr4Lexer ( cf2AntlrLex ) where

import Prelude hiding ((<>))

import Text.PrettyPrint
import BNFC.CF
import BNFC.Backend.Antlr.RegToAntlrLexer
import BNFC.Backend.Common.NamedVariables

-- | Creates a lexer grammar.
-- Since antlr token identifiers must start with an uppercase symbol,
-- I prepend "Surrogate_id_SYMB_" to the identifier.
-- This introduces risks of clashes if somebody uses the same identifier for
-- user defined tokens. This is not handled.
-- returns the environment because the parser uses it.
cf2AntlrLex :: String -> CF -> (Doc, KeywordEnv)
cf2AntlrLex lexerName cf = (,env) $ vcat
[ prelude lexerName
, cMacros
-- unnamed symbols (those in quotes, not in token definitions)
, lexSymbols env
, restOfLexerGrammar cf
]
where
env = zip (cfgSymbols cf ++ reservedWords cf) $ map (("Surrogate_id_SYMB_" ++) . show) [0 :: Int ..]


-- | File prelude
prelude :: String -> Doc
prelude lexerName = vcat
[ "// Lexer definition for use with Antlr4"
, "lexer grammar" <+> text lexerName <> ";"
]

--For now all categories are included.
--Optimally only the ones that are used should be generated.
cMacros :: Doc
cMacros = vcat
[ "// Predefined regular expressions in BNFC"
, frg "LETTER : CAPITAL | SMALL"
, frg "CAPITAL : [A-Z\\u00C0-\\u00D6\\u00D8-\\u00DE]"
, frg "SMALL : [a-z\\u00DF-\\u00F6\\u00F8-\\u00FF]"
, frg "DIGIT : [0-9]"
]
where frg a = "fragment" <+> a <+> ";"

escapeChars :: String -> String
escapeChars = concatMap escapeCharInSingleQuotes

-- |
-- >>> lexSymbols [("foo","bar")]
-- bar : 'foo' ;
-- >>> lexSymbols [("\\","bar")]
-- bar : '\\' ;
-- >>> lexSymbols [("/","bar")]
-- bar : '/' ;
-- >>> lexSymbols [("~","bar")]
-- bar : '~' ;
lexSymbols :: KeywordEnv -> Doc
lexSymbols ss = vcat $ map transSym ss
where
transSym (s,r) = text r <> " : '" <> text (escapeChars s) <> "' ;"

-- | Writes rules for user defined tokens, and, if used, the predefined BNFC tokens.
restOfLexerGrammar :: CF -> Doc
restOfLexerGrammar cf = vcat
[ lexComments (comments cf)
, ""
, userDefTokens
, ifString strdec
, ifChar chardec
, ifC catDouble [
"// Double predefined token type",
"DOUBLE : DIGIT+ '.' DIGIT+ ('e' '-'? DIGIT+)?;"
]
, ifC catInteger [
"//Integer predefined token type",
"INTEGER : DIGIT+;"
]
, ifC catIdent [
"// Identifier token type" ,
"fragment" ,
"IDENTIFIER_FIRST : LETTER | '_';",
"IDENT : IDENTIFIER_FIRST (IDENTIFIER_FIRST | DIGIT)*;"
]
, "// Whitespace"
, "WS : (' ' | '\\r' | '\\t' | '\\n' | '\\f')+ -> skip;"
, "// Escapable sequences"
, "fragment"
, "Escapable : ('\"' | '\\\\' | 'n' | 't' | 'r' | 'f');"
, "ErrorToken : . ;"
, ifString stringmodes
, ifChar charmodes
]
where
ifC cat s = if isUsedCat cf (TokenCat cat) then vcat s else ""
ifString = ifC catString
ifChar = ifC catChar
strdec = [ "// String token type"
, "STRING : '\"' -> more, mode(STRINGMODE);"
]
chardec = ["CHAR : '\\'' -> more, mode(CHARMODE);"]
userDefTokens = vcat
[ text name <> " : " <> text (printRegJLex exp) <> ";"
| (name, exp) <- tokenPragmas cf ]
stringmodes = [ "mode STRESCAPE;"
, "STRESCAPED : Escapable -> more, popMode ;"
, "mode STRINGMODE;"
, "STRINGESC : '\\\\' -> more , pushMode(STRESCAPE);"
, "STRINGEND : '\"' -> type(STRING), mode(DEFAULT_MODE);"
, "STRINGTEXT : ~[\"\\\\] -> more;"
]
charmodes = [ "mode CHARMODE;"
, "CHARANY : ~['\\\\] -> more, mode(CHAREND);"
, "CHARESC : '\\\\' -> more, pushMode(CHAREND),pushMode(ESCAPE);"
, "mode ESCAPE;"
, "ESCAPED : (Escapable | '\\'') -> more, popMode ;"
, "mode CHAREND;"
, "CHARENDC : '\\'' -> type(CHAR), mode(DEFAULT_MODE);"
]

lexComments :: ([(String, String)], [String]) -> Doc
lexComments ([],[]) = ""
lexComments (m,s) = vcat
(prod "COMMENT_antlr_builtin" lexSingleComment s ++
prod "MULTICOMMENT_antlr_builtin" lexMultiComment m )

where
prod bg lc ty = [bg, ": ("] ++ punctuate "|" (map lc ty) ++ skiplex
skiplex = [") -> skip;"]

-- | Create lexer rule for single-line comments.
--
-- >>> lexSingleComment "--"
-- '--' ~[\r\n]* (('\r'? '\n')|EOF)
--
-- >>> lexSingleComment "\""
-- '"' ~[\r\n]* (('\r'? '\n')|EOF)
lexSingleComment :: String -> Doc
lexSingleComment c =
"'" <>text (escapeChars c) <> "' ~[\\r\\n]* (('\\r'? '\\n')|EOF)"

-- | Create lexer rule for multi-lines comments.
--
-- There might be a possible bug here if a language includes 2 multi-line
-- comments. They could possibly start a comment with one character and end it
-- with another. However this seems rare.
--
-- >>> lexMultiComment ("{-", "-}")
-- '{-' (.)*? '-}'
--
-- >>> lexMultiComment ("\"'", "'\"")
-- '"\'' (.)*? '\'"'
lexMultiComment :: (String, String) -> Doc
lexMultiComment (b,e) =
"'" <> text (escapeChars b)
<>"' (.)*? '"<> text (escapeChars e)
<> "'"
Loading
Loading