Skip to content
Open
Show file tree
Hide file tree
Changes from all commits
Commits
Show all changes
43 commits
Select commit Hold shift + click to select a range
b7af04d
First commit to add Scala Backend
juanpaps03 Sep 30, 2024
15ebbed
Added Scala to command doc output
juanpaps03 Sep 30, 2024
ba6278a
using CFtoScalaAbs.hs
juanpaps03 Oct 2, 2024
3fdf4d3
Update BNFC.cabal
WilliamOlsen13 Oct 3, 2024
764b662
Update Options.hs
WilliamOlsen13 Oct 3, 2024
a21d53f
Advance processing data object
juanpaps03 Oct 7, 2024
73101b0
Update Abs to be more Scala ish
juanpaps03 Oct 10, 2024
5900317
Change Abs to match Scala syntax example
juanpaps03 Oct 14, 2024
ed63901
Add auxiliar functions to print Data in file
juanpaps03 Oct 30, 2024
3cfa7a2
comment unnecesary code in scala
juanpaps03 Oct 30, 2024
d8be28c
Base of Scala Lexer
juanpaps03 Dec 10, 2024
25d7236
working on Calc ScalaLex
juanpaps03 Feb 11, 2025
c22b42d
add scala lexer working
juanpaps03 Feb 21, 2025
202578c
primera version de parser
juanpaps03 Mar 16, 2025
f955318
improved parser
juanpaps03 Mar 20, 2025
c057531
working version of parser with calc.cf
juanpaps03 Mar 20, 2025
ce75ef8
add integer and removed unused function
juanpaps03 Mar 20, 2025
b897701
version with simple rules working better
juanpaps03 Mar 20, 2025
4b4a2e8
fix base function as extra def in parser
juanpaps03 Mar 24, 2025
fd7c876
fix integer rule creation
juanpaps03 Mar 25, 2025
7c299aa
fix AST, remove unused code
juanpaps03 Mar 25, 2025
55b5378
Fix AST formatting
WilliamOlsen13 Mar 27, 2025
286eccb
Fix Parser formatting
WilliamOlsen13 Mar 27, 2025
0488a92
Fix Lexer formatting
WilliamOlsen13 Mar 27, 2025
cac7fe1
change in parser AST to work with LBNF example
juanpaps03 Mar 27, 2025
41b17c3
fixes on parser scala generator
juanpaps03 Apr 1, 2025
9f414f7
fix minor problems and add utils file
juanpaps03 Apr 3, 2025
be98d95
changes to make the parser more scalable
juanpaps03 Apr 5, 2025
f9e1131
minor fixes and clean up
juanpaps03 Apr 5, 2025
08777db
improvement in LBNF parser generation
juanpaps03 Apr 6, 2025
7a488bb
almost there with lbnf parser generation
juanpaps03 Apr 7, 2025
ba4bccd
improves in LBNF compiler generation
juanpaps03 Apr 8, 2025
d980756
minichi working
juanpaps03 Apr 12, 2025
2d6e3af
chi funcionando para casos basicos
juanpaps03 Apr 12, 2025
1d01fe5
chi working better
juanpaps03 Apr 13, 2025
a7825ca
chi working with if and calc
juanpaps03 Apr 14, 2025
10e8832
fix cabal warnings
juanpaps03 Apr 14, 2025
d488def
fix case with multiple operators in chi
juanpaps03 Apr 14, 2025
d40fc4c
fix case of !false in chi
juanpaps03 Apr 14, 2025
54670fa
fix types order error in lexer
juanpaps03 Apr 14, 2025
92bb9f8
clean up a little bit and fix cpp parser generation
juanpaps03 Apr 16, 2025
289a6de
Merge branch 'feature/scala/abs' into tesis-master
juanpaps03 Apr 16, 2025
8d7f698
remove abs
juanpaps03 Apr 16, 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
6 changes: 6 additions & 0 deletions .gitignore
Original file line number Diff line number Diff line change
Expand Up @@ -172,3 +172,9 @@ cabal.sandbox.config
/testing/regression-tests/266_define/nostl-2.9.0/

/testing/regression-tests/comments/ocaml/

ignore-dir/

.DS_Store
.vscode
.metals
8 changes: 8 additions & 0 deletions source/BNFC.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -272,6 +272,14 @@ library
-- Pygments backend
BNFC.Backend.Pygments

-- Scala backend
BNFC.Backend.Scala
BNFC.Backend.Scala.Utils
BNFC.Backend.Scala.CFtoScalaLex
BNFC.Backend.Scala.CFtoScalaLexToken
BNFC.Backend.Scala.CFtoScalaParser
BNFC.Backend.Scala.CFtoScalaParserAST

-- Agda backend
BNFC.Backend.Agda

Expand Down
2 changes: 2 additions & 0 deletions source/main/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -26,6 +26,7 @@ import BNFC.Backend.Latex
import BNFC.Backend.OCaml
import BNFC.Backend.Pygments
import BNFC.Backend.TreeSitter
import BNFC.Backend.Scala
import BNFC.CF (CF)
import BNFC.GetCF
import BNFC.Options hiding (make, Backend)
Expand Down Expand Up @@ -83,3 +84,4 @@ maketarget = \case
TargetPygments -> makePygments
TargetCheck -> error "impossible"
TargetTreeSitter -> makeTreeSitter
TargetScala -> makeScala
26 changes: 26 additions & 0 deletions source/src/BNFC/Backend/Scala.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,26 @@
module BNFC.Backend.Scala where

import Prelude hiding ((<>))

import BNFC.Backend.Base (mkfile, Backend)
import BNFC.CF
import BNFC.Options hiding (Backend)
-- import BNFC.Backend.Scala.CFtoScalaAbs (cf2ScalaAbs)
import BNFC.Backend.Scala.CFtoScalaLex (cf2ScalaLex)
import BNFC.Backend.Scala.CFtoScalaLexToken (cf2ScalaLexToken)
import BNFC.Backend.Scala.CFtoScalaParser (cf2ScalaParser)
import BNFC.Backend.Scala.CFtoScalaParserAST (cf2ScalaParserAST)

-- | Entrypoint for the Scala backend.

makeScala :: SharedOptions -> CF -> Backend
makeScala opts cf = do
-- mkfile (name ++ ".scala") comment $ cf2ScalaAbs opts cf
mkfile (name ++ "LexToken.scala") comment $ cf2ScalaLexToken opts cf
mkfile (name ++ "Lex.scala") comment $ cf2ScalaLex opts cf
mkfile (name ++ "Parser.scala") comment $ cf2ScalaParser opts cf
mkfile (name ++ "ParserAST.scala") comment $ cf2ScalaParserAST opts cf
where name = lang opts

comment :: String -> String
comment = ("// " ++)
204 changes: 204 additions & 0 deletions source/src/BNFC/Backend/Scala/CFtoScalaLex.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,204 @@
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE PatternGuards #-}
{-# LANGUAGE OverloadedStrings #-}

{-
BNF Converter: Scala Lextract syntax
Copyright (Scala) 2024 Author: Juan Pablo Poittevin, Guillermo Poladura

Description : This module generates the Scala Lextract Syntax
tree classes. Using Scala Parser Combinator

Author : Juan Pablo Poittevin, Guillermo Poladura
Created : 30 September, 2024
-}

module BNFC.Backend.Scala.CFtoScalaLex (cf2ScalaLex) where

import Prelude hiding ((<>))

import BNFC.Utils (symbolToName)
import BNFC.CF
import BNFC.PrettyPrint
import BNFC.Options
import BNFC.Backend.Common (unicodeAndSymbols)
import Data.List (intercalate)
import Data.Char (toLower)
import GHC.OldList (nub)
import GHC.Unicode (toUpper)
import BNFC.Backend.Scala.Utils (scalaReserverWords, mapManualTypeMap, scalaBNFCReserverWords, applyToRepeated)
import Data.Maybe (fromMaybe)

-- | Converts a string to lowercase
toLowerString :: String -> String
toLowerString s = map toLower s

-- | Main function that generates the Scala lexer code
cf2ScalaLex :: SharedOptions -> CF -> Doc
cf2ScalaLex Options{ lang } cf = vcat $
-- Generate header and imports
imports lang ++
-- Generate error and location classes
addExtraClasses ++
-- Start the WorkflowLexer object
initWorkflowClass ++
-- Indent the class contents
[nest 4 $ vcat $
-- Add apply function
getApplyFunction ++
-- Add tokens function
getTokensFunction (keyWords ++ symbs ++ liters) ++
-- Add parser functions for literals
map addParserFunction liters ++
-- Add keyword parsers
map getBaseLexs (keyWords ++ symbs)
] ++
-- End the WorkflowLexer object
endWorkflowClass
where
keyWords = reservedWords cf
symbs = unicodeAndSymbols cf
liters = nub $ literals cf

-- | Generate a parser function for a specific literal type
addParserFunction :: String -> Doc
addParserFunction liter
| liter == catInteger = getIntegerFunction
| liter == catDouble = getDoubleFunction
| liter == catIdent = getIdentifiersFunction
| liter == catString = getLiteralsFunction
| liter == catChar = getLiteralFunction
| otherwise = empty

-- | Generate the imports section
imports :: String -> [Doc]
imports name = [
text $ "package " ++ name ++ ".workflowtoken." ++ name ++ "Lex",
text "",
text "import scala.util.parsing.combinator.RegexParsers"
]

-- | Generate error and location classes
addExtraClasses :: [Doc]
addExtraClasses = [
text "",
text "sealed trait WorkflowCompilationError",
text "case class WorkflowLexerError(location: Location, msg: String) extends WorkflowCompilationError",
text "case class WorkflowParserError(location: Location, msg: String) extends WorkflowCompilationError",
text "",
text "case class Location(line: Int, column: Int) {",
nest 4 $ text "override def toString = s\"$line:$column\"",
text "}"
]

-- | Start the WorkflowLexer object
initWorkflowClass :: [Doc]
initWorkflowClass = [
text "",
text "object WorkflowLexer extends RegexParsers {"
]

-- | End the WorkflowLexer object
endWorkflowClass :: [Doc]
endWorkflowClass = [
text "}"
]

-- | Generate the apply function
getApplyFunction :: [Doc]
getApplyFunction = [
text "def apply(code: String): Either[WorkflowLexerError, List[WorkflowToken]] = {",
nest 4 $ text "parse(tokens, code) match {",
nest 8 $ text "case NoSuccess(msg, next) => Left(WorkflowLexerError(Location(next.pos.line, next.pos.column), msg))",
nest 8 $ text "case Success(result, next) => Right(result)",
nest 4 $ text "}",
text "}"
]

-- | Generate the function for parsing identifiers
getIdentifiersFunction :: Doc
getIdentifiersFunction = vcat [
text "",
text "def ident: Parser[IDENT] = {",
nest 4 $ text "\"[a-zA-Z_][a-zA-Z0-9_]*\".r ^^ { str => IDENT(str) }",
text "}"
]

-- | Generate the function for parsing integers
getIntegerFunction :: Doc
getIntegerFunction = vcat [
text "",
text "def integer: Parser[INTEGER] = {",
nest 4 $ text "\"[0-9]+\".r ^^ {i => INTEGER(i)}",
text "}"
]

-- | Generate the function for parsing double values
getDoubleFunction :: Doc
getDoubleFunction = vcat [
text "",
text "def double: Parser[DOUBLE] = {",
nest 4 $ text "\"[0-9]+.[0-9]+\".r ^^ {i => DOUBLE(i)}",
text "}"
]

-- | Generate the function for parsing string literals
getLiteralsFunction :: Doc
getLiteralsFunction = vcat [
text "",
text "def string: Parser[STRING] = {",
nest 4 $ text "\"\\\"[^\\\"]*\\\"\".r ^^ { str =>",
nest 8 $ text "val content = str.substring(1, str.length - 1)",
nest 8 $ text "STRING(content)",
nest 4 $ text "}",
text "}"
]

-- | Generate the function for parsing character literals
getLiteralFunction :: Doc
getLiteralFunction = vcat [
text "",
text "def char: Parser[CHAR] = {",
nest 4 $ text "\"\\\'[^\\\']*\\\'\".r ^^ { str =>",
nest 8 $ text "val content = str.substring(1, str.length - 1)",
nest 8 $ text "CHAR(content)",
nest 4 $ text "}",
text "}"
]

-- | Get a symbol name from a string
getSymbFromName :: String -> String
getSymbFromName s =
case symbolToName s of
Just s -> s
_ -> map toUpper s

-- | Generate the tokens function
getTokensFunction :: [String] -> [Doc]
getTokensFunction tokens = [
text "",
text "def tokens: Parser[List[WorkflowToken]] = {",
nest 4 $ text $ "phrase(rep1( " ++ intercalate " | " proccesedRepetedSymbs ++ "))",
text "}"
]
where
proccesedRepetedSymbs = reverse $ applyToRepeated ("p" ++) $ reverse $ getListTokensNames tokens

-- | Get the lowercase symbol name
getTokenName :: String -> String
getTokenName s = fromMaybe (toLowerString $ getSymbFromName s) $ scalaReserverWords $ toLowerString $ getSymbFromName s

-- | Get a list of symbol names
getListTokensNames :: [String] -> [String]
getListTokensNames = map getTokenName

-- | Generate a keyword parser for a symbol
getBaseLexs :: String -> Doc
getBaseLexs symb =
text "" $+$
text ("def " ++ defName ++ " = positioned { \"" ++ toLowerString symb ++ "\" ^^ (_ => " ++ param' ++ "()) }")
where
param = map toUpper $ getSymbFromName symb
param' = fromMaybe param $ mapManualTypeMap param
defName = fromMaybe (getTokenName symb) $ scalaBNFCReserverWords $ getTokenName symb

81 changes: 81 additions & 0 deletions source/src/BNFC/Backend/Scala/CFtoScalaLexToken.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,81 @@

{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE PatternGuards #-}
{-# LANGUAGE OverloadedStrings #-}

{-
BNF Converter: Scala Lextract syntax
Copyright (Scala) 2024 Author: Juan Pablo Poittevin

Description : This module generates the Scala Lextract Syntax
tree classes. It generates both a Header file
and an Implementation file

Author : Juan Pablo Poittevin
Created : 30 September, 2024
-}

module BNFC.Backend.Scala.CFtoScalaLexToken (cf2ScalaLexToken) where

import Prelude hiding ((<>))

import BNFC.CF
import BNFC.PrettyPrint
import BNFC.Options
import BNFC.Backend.Common (unicodeAndSymbols)
import BNFC.Utils (symbolToName)
import Data.Char (toUpper)
import Data.List (nub)
import BNFC.Backend.Scala.Utils (scalaReserverWords, mapManualTypeMap)
import Data.Maybe (fromMaybe)

cf2ScalaLexToken
:: SharedOptions
-> CF
-> Doc
cf2ScalaLexToken Options{ lang } cf = vsep . concat $
[
headers lang
, [text $ concat $ map generateSymbClass (symbs)]
, [generateStringClasses liters]
, [generateKeyWordClasses (keyWords ++ ["empty"])]
-- , [text $ "Symbols: " ++ show symbs]
-- , [text $ "Literals: " ++ show liters]
-- , [text $ "Keywords: " ++ show keyWords]
]
where
liters = nub $ literals cf
symbs = unicodeAndSymbols cf
keyWords = reservedWords cf


generateSymbClass :: String -> String
generateSymbClass symb = case symbolToName symb of
Just s -> "case class " ++ fromMaybe s (scalaReserverWords s) ++ "() extends WorkflowToken \n"
Nothing -> mempty


generateKeyWordClasses :: [String] -> Doc
generateKeyWordClasses params = text $ concat $ map generateKeyWordClass params

generateKeyWordClass :: String -> String
generateKeyWordClass key = "case class " ++ param' ++ "() extends WorkflowToken \n"
where
param = map toUpper key
param' = fromMaybe param $ mapManualTypeMap param


generateStringClasses :: [String] -> Doc
generateStringClasses params = text $ concat $ map generateStringClass params

generateStringClass :: String -> String
generateStringClass param = "case class " ++ (map toUpper param) ++ "(str: String) extends WorkflowToken \n"

headers :: String -> [Doc]
headers name = [
text $ "package " ++ name ++ ".workflowtoken." ++ name ++ "Lex"
, "import scala.util.parsing.input.Positional"
, "sealed trait WorkflowToken extends Positional"
]


Loading
Loading