project-structure #1

Merged
MisterChaos69 merged 2 commits from project-structure into master 2024-05-02 08:28:04 +00:00
8 changed files with 477 additions and 0 deletions

23
.gitignore vendored Normal file
View File

@ -0,0 +1,23 @@
dist
dist-*
cabal-dev
*.o
*.hi
*.hie
*.chi
*.chs.h
*.dyn_o
*.dyn_hi
.hpc
.hsenv
.cabal-sandbox/
cabal.sandbox.config
*.prof
*.aux
*.hp
*.eventlog
.stack-work/
cabal.project.local
cabal.project.local~
.HTF/
.ghc.environment.*

View File

@ -1,3 +1,14 @@
# MiniJavaCompiler
It's a compiler for a minimal version of Java with watered down syntax.
Written in Haskell.
# Cabal Commands
run main
```
cabal run
```
run tests
```
cabal test
```

17
Test/TestLexer.hs Normal file
View File

@ -0,0 +1,17 @@
module TestLexer(tests) where
import Test.HUnit
import Parser.Lexer
testCommentSomething = TestCase $ assertEqual "scan /*Something*/" [Comment "/*Something*/"] $ alexScanTokens "/*Something*/"
testEmptyComment = TestCase $ assertEqual "scan /*x*/" [Comment "/**/"] $ alexScanTokens "/**/"
testLineComment = TestCase $ assertEqual "scan // comment" [Comment "// comment"] $ alexScanTokens "// comment"
tests = TestList [
TestLabel "TestCommentSomething" testCommentSomething,
TestLabel "TestEmptyComment" testEmptyComment,
TestLabel "TestLineComment" testLineComment
]

11
Test/TestSuite.hs Normal file
View File

@ -0,0 +1,11 @@
module Main where
import Test.HUnit
import Parser.Lexer
import TestLexer
otherTest = TestCase $ assertEqual "math" (4+3) 7
tests = TestList [TestLabel "TestLexer" TestLexer.tests, TestLabel "mathTest" otherTest]
main = do runTestTTAndExit Main.tests

25
project.cabal Normal file
View File

@ -0,0 +1,25 @@
name: MiniJavaCompiler
version: 0.1.0.0
build-type: Simple
cabal-version: >= 1.10
Synopsis: A compiler for a minimal version of Java with watered down syntax.
executable compiler
main-is: Main.hs
build-depends: base,
array,
HUnit
default-language: Haskell2010
hs-source-dirs: src
build-tool-depends: alex:alex, happy:happy
other-modules: Parser.Lexer
test-suite tests
type: exitcode-stdio-1.0
main-is: TestSuite.hs
hs-source-dirs: src,Test
build-depends: base,
array,
HUnit
build-tool-depends: alex:alex, happy:happy
other-modules: Parser.Lexer, TestLexer

6
src/Main.hs Normal file
View File

@ -0,0 +1,6 @@
module Main where
import Parser.Lexer
main = do
print $ alexScanTokens "/**/"

360
src/Parser/JavaParser.y Normal file
View File

@ -0,0 +1,360 @@
{
module Parser.JavaParser (parse) where
--import AbsSyn
import Parser.Lexer
}
%name parse
%tokentype { Token }
%error { parseError }
%token
BOOLEAN { BOOLEAN }
BREAK { BREAK }
CASE { CASE }
CHAR { CHAR }
CLASS { CLASS}
IDENTIFIER { IDENTIFIER $$}
INTLITERAL { INTLITERAL $$}
DOT { DOT }
MOD { MOD }
TIMESEQUAL { TIMESEQUAL }
GREATEREQUAL { GREATEREQUAL }
WHILE { WHILE }
PUBLIC { PUBLIC }
VOID { VOID }
EQUAL { EQUAL }
XOR { XOR }
RBRACE { RBRACE }
THIS { THIS }
STATIC { STATIC }
PROTECTED { PROTECTED }
TILDE { TILDE }
MUL { MUL }
MINUS { MINUS }
EXCLMARK { EXCLMARK }
IF { IF }
ELSE { ELSE }
DIVIDEEQUAL { DIVIDEEQUAL }
NEW { NEW }
LBRACKET { LBRACKET }
JNULL { JNULL }
BOOLLITERAL { BOOLLITERAL }
DIV { DIV }
LOGICALOR { LOGICALOR }
NOTEQUAL { NOTEQUAL }
INSTANCEOF { INSTANCEOF }
ANDEQUAL { ANDEQUAL }
ASSIGN { ASSIGN }
DECREMENT { DECREMENT }
STRINGLITERAL { STRINGLITERAL }
CHARLITERAL { CHARLITERAL }
AND { AND }
XOREQUAL { XOREQUAL }
RETURN { RETURN }
QUESMARK { QUESMARK }
SHIFTLEFTEQUAL { SHIFTLEFTEQUAL }
RBRACKET { RBRACKET }
COMMA { COMMA }
MINUSEQUAL { MINUSEQUAL }
INCREMENT { INCREMENT }
LBRACE { LBRACE }
LESSEQUAL { LESSEQUAL }
PLUS { PLUS }
PRIVATE { PRIVATE }
MODULOEQUAL { MODULOEQUAL }
GREATER { GREATER }
OR { OR }
INT { INT }
ABSTRACT { ABSTRACT }
SEMICOLON { SEMICOLON }
SIGNEDSHIFTRIGHTEQUAL { SIGNEDSHIFTRIGHTEQUAL }
UNSIGNEDSHIFTRIGHTEQUAL { UNSIGNEDSHIFTRIGHTEQUAL }
PLUSEQUAL { PLUSEQUAL }
OREQUAL { OREQUAL }
COLON { COLON }
LESS { LESS }
%%
compilationunit : typedeclarations { }
typedeclarations : typedeclaration { }
| typedeclarations typedeclaration { }
name : qualifiedname { }
| simplename { }
typedeclaration : classdeclaration { }
qualifiedname : name DOT IDENTIFIER { }
simplename : IDENTIFIER { }
classdeclaration : CLASS IDENTIFIER classbody { }
| modifiers CLASS IDENTIFIER classbody { }
classbody : LBRACKET RBRACKET { ([], []) }
| LBRACKET classbodydeclarations RBRACKET { }
modifiers : modifier { }
| modifiers modifier { }
classbodydeclarations : classbodydeclaration { }
| classbodydeclarations classbodydeclaration{ }
modifier : PUBLIC { }
| PROTECTED { }
| PRIVATE { }
| STATIC { }
| ABSTRACT { }
classtype : classorinterfacetype{ }
classbodydeclaration : classmemberdeclaration { }
| constructordeclaration { }
classorinterfacetype : name{ }
classmemberdeclaration : fielddeclaration { }
| methoddeclaration { }
constructordeclaration : constructordeclarator constructorbody { }
| modifiers constructordeclarator constructorbody { }
fielddeclaration : type variabledeclarators SEMICOLON { }
| modifiers type variabledeclarators SEMICOLON { }
methoddeclaration : methodheader methodbody { }
block : LBRACKET RBRACKET { }
| LBRACKET blockstatements RBRACKET { }
constructordeclarator : simplename LBRACE RBRACE { }
| simplename LBRACE formalparameterlist RBRACE { }
constructorbody : LBRACKET RBRACKET { }
| LBRACKET explicitconstructorinvocation RBRACKET { }
| LBRACKET blockstatements RBRACKET { }
| LBRACKET explicitconstructorinvocation blockstatements RBRACKET { }
methodheader : type methoddeclarator { }
| modifiers type methoddeclarator { }
| VOID methoddeclarator { }
| modifiers VOID methoddeclarator { }
type : primitivetype { }
| referencetype { }
variabledeclarators : variabledeclarator { }
| variabledeclarators COMMA variabledeclarator { }
methodbody : block { }
| SEMICOLON { }
blockstatements : blockstatement { }
| blockstatements blockstatement { }
formalparameterlist : formalparameter { }
| formalparameterlist COMMA formalparameter{ }
explicitconstructorinvocation : THIS LBRACE RBRACE SEMICOLON { }
| THIS LBRACE argumentlist RBRACE SEMICOLON { }
classtypelist : classtype { }
| classtypelist COMMA classtype { }
methoddeclarator : IDENTIFIER LBRACE RBRACE { }
| IDENTIFIER LBRACE formalparameterlist RBRACE { }
primitivetype : BOOLEAN { }
| numerictype { }
referencetype : classorinterfacetype { }
variabledeclarator : variabledeclaratorid { }
| variabledeclaratorid ASSIGN variableinitializer { }
blockstatement : localvariabledeclarationstatement { }
| statement { }
formalparameter : type variabledeclaratorid { }
argumentlist : expression { }
| argumentlist COMMA expression { }
numerictype : integraltype { }
variabledeclaratorid : IDENTIFIER { }
variableinitializer : expression { }
localvariabledeclarationstatement : localvariabledeclaration SEMICOLON { }
statement : statementwithouttrailingsubstatement{ }
| ifthenstatement { }
| ifthenelsestatement { }
| whilestatement { }
expression : assignmentexpression { }
integraltype : INT { }
| CHAR { }
localvariabledeclaration : type variabledeclarators { }
statementwithouttrailingsubstatement : block { }
| emptystatement { }
| expressionstatement { }
| returnstatement { }
ifthenstatement : IF LBRACE expression RBRACE statement { }
ifthenelsestatement : IF LBRACE expression RBRACE statementnoshortif ELSE statement { }
whilestatement : WHILE LBRACE expression RBRACE statement { }
assignmentexpression : conditionalexpression { }
| assignment{ }
emptystatement : SEMICOLON { }
expressionstatement : statementexpression SEMICOLON { }
returnstatement : RETURN SEMICOLON { }
| RETURN expression SEMICOLON { }
statementnoshortif : statementwithouttrailingsubstatement { }
| ifthenelsestatementnoshortif { }
| whilestatementnoshortif { }
conditionalexpression : conditionalorexpression { }
| conditionalorexpression QUESMARK expression COLON conditionalexpression { }
assignment :lefthandside assignmentoperator assignmentexpression { }
statementexpression : assignment { }
| preincrementexpression { }
| predecrementexpression { }
| postincrementexpression { }
| postdecrementexpression { }
| methodinvocation { }
| classinstancecreationexpression { }
ifthenelsestatementnoshortif :IF LBRACE expression RBRACE statementnoshortif
ELSE statementnoshortif { }
whilestatementnoshortif : WHILE LBRACE expression RBRACE statementnoshortif { }
conditionalorexpression : conditionalandexpression { }
| conditionalorexpression LOGICALOR conditionalandexpression{ }
lefthandside : name { }
assignmentoperator : ASSIGN{ }
| TIMESEQUAL { }
| DIVIDEEQUAL { }
| MODULOEQUAL { }
| PLUSEQUAL { }
| MINUSEQUAL { }
| SHIFTLEFTEQUAL { }
| SIGNEDSHIFTRIGHTEQUAL { }
| UNSIGNEDSHIFTRIGHTEQUAL { }
| ANDEQUAL { }
| XOREQUAL { }
| OREQUAL{ }
preincrementexpression : INCREMENT unaryexpression { }
predecrementexpression : DECREMENT unaryexpression { }
postincrementexpression : postfixexpression INCREMENT { }
postdecrementexpression : postfixexpression DECREMENT { }
methodinvocation : name LBRACE RBRACE { }
| name LBRACE argumentlist RBRACE { }
| primary DOT IDENTIFIER LBRACE RBRACE { }
| primary DOT IDENTIFIER LBRACE argumentlist RBRACE { }
classinstancecreationexpression : NEW classtype LBRACE RBRACE { }
| NEW classtype LBRACE argumentlist RBRACE { }
conditionalandexpression : inclusiveorexpression { }
fieldaccess : primary DOT IDENTIFIER { }
unaryexpression : preincrementexpression { }
| predecrementexpression { }
| PLUS unaryexpression { }
| MINUS unaryexpression { }
| unaryexpressionnotplusminus { }
postfixexpression : primary { }
| name { }
| postincrementexpression { }
| postdecrementexpression{ }
primary : primarynonewarray { }
inclusiveorexpression : exclusiveorexpression { }
| inclusiveorexpression OR exclusiveorexpression { }
primarynonewarray : literal { }
| THIS { }
| LBRACE expression RBRACE { }
| classinstancecreationexpression { }
| fieldaccess { }
| methodinvocation { }
unaryexpressionnotplusminus : postfixexpression { }
| TILDE unaryexpression { }
| EXCLMARK unaryexpression { }
| castexpression{ }
exclusiveorexpression : andexpression { }
| exclusiveorexpression XOR andexpression { }
literal : INTLITERAL { }
| BOOLLITERAL { }
| CHARLITERAL { }
| STRINGLITERAL { }
| JNULL { }
castexpression : LBRACE primitivetype RBRACE unaryexpression { }
| LBRACE expression RBRACE unaryexpressionnotplusminus{ }
andexpression : equalityexpression { }
| andexpression AND equalityexpression { }
equalityexpression : relationalexpression { }
| equalityexpression EQUAL relationalexpression { }
| equalityexpression NOTEQUAL relationalexpression { }
relationalexpression : shiftexpression { }
| relationalexpression LESS shiftexpression { }
| relationalexpression GREATER shiftexpression { }
| relationalexpression LESSEQUAL shiftexpression { }
| relationalexpression GREATEREQUAL shiftexpression { }
| relationalexpression INSTANCEOF referencetype { }
shiftexpression : additiveexpression { }
additiveexpression : multiplicativeexpression { }
| additiveexpression PLUS multiplicativeexpression { }
| additiveexpression MINUS multiplicativeexpression { }
multiplicativeexpression : unaryexpression { }
| multiplicativeexpression MUL unaryexpression { }
| multiplicativeexpression DIV unaryexpression { }
| multiplicativeexpression MOD unaryexpression { }
{
parseError :: [Token] -> a
parseError _ = error "Parse error"
}

24
src/Parser/Lexer.x Normal file
View File

@ -0,0 +1,24 @@
{
module Parser.Lexer(Token(..), alexScanTokens) where
}
%wrapper "basic"
$digit = 0-9
$alpha = [a-zA-Z]
$alphanum = [a-zA-Z0-9]
tokens :-
$white ;
"/*"(.|\n)*"*/" { \s -> Comment s }
"//".* {\s -> Comment s}
{
data Token
= Comment String
| Different
deriving(Eq,Show)
}