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 185 additions and 11 deletions
Showing only changes of commit d59594ab74 - Show all commits

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 "/**/"

View File

@ -1,7 +1,7 @@
{
module JavaParser (parse) where
import AbsSyn
import Lexer
module Parser.JavaParser (parse) where
--import AbsSyn
import Parser.Lexer
}
%name parse
@ -9,14 +9,71 @@ import Lexer
%error { parseError }
%token
BOOLEAN { BOOLEAN }
BREAK { BREAK }
CASE { CASE }
CHAR { CHAR }
CLASS { CLASS}
IDENTIFIER { IDENTIFIER $$}
INTLITERAL { INTLITERAL $$}
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 { }

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)
}