Compare commits

..

10 Commits

7 changed files with 439 additions and 153 deletions

View File

@ -11,9 +11,23 @@ testEmptyComment = TestCase $ assertEqual "scan '/*x*/'" emptyTokenList $ alex
testLineComment = TestCase $ assertEqual "scan '// comment'" emptyTokenList $ alexScanTokens "// comment" testLineComment = TestCase $ assertEqual "scan '// comment'" emptyTokenList $ alexScanTokens "// comment"
testLineCommentEnds = TestCase $ assertEqual "scan '// com\\n'" emptyTokenList $ alexScanTokens "// com\n" testLineCommentEnds = TestCase $ assertEqual "scan '// com\\n'" emptyTokenList $ alexScanTokens "// com\n"
testIdentifier = TestCase $ assertEqual "scan 'identifier'" [Identifier "identifier"] $ alexScanTokens "identifier" testIdentifier = TestCase $ assertEqual "scan 'identifier'" [IDENTIFIER "identifier"] $ alexScanTokens "identifier"
testShortIdentifier = TestCase $ assertEqual "scan 'i'" [Identifier "i"] $ alexScanTokens "i" testShortIdentifier = TestCase $ assertEqual "scan 'i'" [IDENTIFIER "i"] $ alexScanTokens "i"
testIdentifierWithNumber = TestCase $ assertEqual "scan 'i2'" [Identifier "i2"] $ alexScanTokens "i2" testIdentifierWithNumber = TestCase $ assertEqual "scan 'i2'" [IDENTIFIER "i2"] $ alexScanTokens "i2"
testKeywordBreak = TestCase $ assertEqual "scan 'break'" [BREAK] $ alexScanTokens "break"
testKeywordInt = TestCase $ assertEqual "scan 'int'" [INT] $ alexScanTokens "int"
testIntLiteral = TestCase $ assertEqual "scan '234'" [INTEGERLITERAL 234] $ alexScanTokens "234"
testIntLiteral2 = TestCase $ assertEqual "scan '54_2'" [INTEGERLITERAL 542] $ alexScanTokens "54_2"
testCharLiteral = TestCase $ assertEqual "scan ''f''" [CHARLITERAL 'f'] $ alexScanTokens "'f'"
testBoolLiteralTrue = TestCase $ assertEqual "scan 'true'" [BOOLLITERAL True] $ alexScanTokens "true"
testBoolLiteralFalse = TestCase $ assertEqual "scan 'false'" [BOOLLITERAL False] $ alexScanTokens "false"
testLBrace = TestCase $ assertEqual "scan '('" [LBRACE] $ alexScanTokens "("
testAnd = TestCase $ assertEqual "scan '&&'" [AND] $ alexScanTokens "&&"
tests = TestList [ tests = TestList [
TestLabel "TestCommentSomething" testCommentSomething, TestLabel "TestCommentSomething" testCommentSomething,
@ -22,5 +36,14 @@ tests = TestList [
TestLabel "TestLineCommentEnds" testLineCommentEnds, TestLabel "TestLineCommentEnds" testLineCommentEnds,
TestLabel "TestIdentifier" testIdentifier, TestLabel "TestIdentifier" testIdentifier,
TestLabel "TestShortIdentifier" testShortIdentifier, TestLabel "TestShortIdentifier" testShortIdentifier,
TestLabel "TestIdentifierWithNumber" testIdentifierWithNumber TestLabel "TestIdentifierWithNumber" testIdentifierWithNumber,
TestLabel "TestKeywordBreak" testKeywordBreak,
TestLabel "TestKeywordInt" testKeywordInt,
TestLabel "TestIntLiteral" testIntLiteral,
TestLabel "TestIntLiteral2" testIntLiteral2,
TestLabel "TestCharLiteral" testCharLiteral,
TestLabel "TestBoolLiteralTrue" testBoolLiteralTrue,
TestLabel "TestBoolLiteralFalse" testBoolLiteralFalse,
TestLabel "TestLBrace" testLBrace,
TestLabel "TestAnd" testAnd
] ]

28
Test/TestParser.hs Normal file
View File

@ -0,0 +1,28 @@
module TestParser(tests) where
import Test.HUnit
import Parser.Lexer
import Parser.JavaParser
import Ast
testSingleEmptyClass = TestCase $
assertEqual "expect single empty class hello" [Class "Hello" [] []] $
parse [CLASS, IDENTIFIER "Hello", LBRACKET, RBRACKET]
testTwoEmptyClasses = TestCase $
assertEqual "expect two empty classes" [Class "Class1" [] [], Class "Class2" [] []] $
parse [CLASS,IDENTIFIER "Class1",LBRACKET,RBRACKET,CLASS,IDENTIFIER "Class2",LBRACKET,RBRACKET]
testBooleanField = TestCase $
assertEqual "expect class with boolean field" [Class "WithBool" [] [VariableDeclaration "boolean" "value" Nothing]] $
parse [CLASS,IDENTIFIER "WithBool",LBRACKET,BOOLEAN,IDENTIFIER "value",SEMICOLON,RBRACKET]
testIntField = TestCase $
assertEqual "expect class with int field" [Class "WithInt" [] [VariableDeclaration "int" "value" Nothing]] $
parse [CLASS,IDENTIFIER "WithInt",LBRACKET,INT,IDENTIFIER "value",SEMICOLON,RBRACKET]
tests = TestList [
testSingleEmptyClass,
testTwoEmptyClasses,
testBooleanField,
testIntField
]

View File

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

View File

@ -12,7 +12,7 @@ executable compiler
default-language: Haskell2010 default-language: Haskell2010
hs-source-dirs: src hs-source-dirs: src
build-tool-depends: alex:alex, happy:happy build-tool-depends: alex:alex, happy:happy
other-modules: Parser.Lexer, Ast other-modules: Parser.Lexer, Parser.JavaParser, Ast
test-suite tests test-suite tests
type: exitcode-stdio-1.0 type: exitcode-stdio-1.0
@ -22,4 +22,8 @@ test-suite tests
array, array,
HUnit HUnit
build-tool-depends: alex:alex, happy:happy build-tool-depends: alex:alex, happy:happy
other-modules: Parser.Lexer, TestLexer other-modules: Parser.Lexer,
Parser.JavaParser,
Ast,
TestLexer
TestParser

View File

@ -5,9 +5,13 @@ type DataType = String
type Identifier = String type Identifier = String
data ParameterDeclaration = ParameterDeclaration DataType Identifier data ParameterDeclaration = ParameterDeclaration DataType Identifier
deriving(Show, Eq)
data VariableDeclaration = VariableDeclaration DataType Identifier (Maybe Expression) data VariableDeclaration = VariableDeclaration DataType Identifier (Maybe Expression)
deriving(Show, Eq)
data Class = Class DataType [MethodDeclaration] [VariableDeclaration] data Class = Class DataType [MethodDeclaration] [VariableDeclaration]
deriving(Show, Eq)
data MethodDeclaration = MethodDeclaration DataType Identifier [ParameterDeclaration] Statement data MethodDeclaration = MethodDeclaration DataType Identifier [ParameterDeclaration] Statement
deriving(Show, Eq)
data Statement = If Expression Statement (Maybe Statement) data Statement = If Expression Statement (Maybe Statement)
| LocalVariableDeclaration VariableDeclaration | LocalVariableDeclaration VariableDeclaration
@ -16,11 +20,13 @@ data Statement = If Expression Statement (Maybe Statement)
| Return (Maybe Expression) | Return (Maybe Expression)
| StatementExpressionStatement StatementExpression | StatementExpressionStatement StatementExpression
| TypedStatement DataType Statement | TypedStatement DataType Statement
deriving(Show, Eq)
data StatementExpression = Assignment Identifier Expression data StatementExpression = Assignment Identifier Expression
| ConstructorCall DataType [Expression] | ConstructorCall DataType [Expression]
| MethodCall Identifier [Expression] | MethodCall Identifier [Expression]
| TypedStatementExpression DataType StatementExpression | TypedStatementExpression DataType StatementExpression
deriving(Show, Eq)
data BinaryOperator = Addition data BinaryOperator = Addition
| Subtraction | Subtraction
@ -38,9 +44,11 @@ data BinaryOperator = Addition
| And | And
| Or | Or
| NameResolution | NameResolution
deriving(Show, Eq)
data UnaryOperator = Not data UnaryOperator = Not
| Minus | Minus
deriving(Show, Eq)
data Expression = IntegerLiteral Int data Expression = IntegerLiteral Int
| CharacterLiteral Char | CharacterLiteral Char
@ -51,4 +59,5 @@ data Expression = IntegerLiteral Int
| UnaryOperation UnaryOperator Expression | UnaryOperation UnaryOperator Expression
| StatementExpressionExpression StatementExpression | StatementExpressionExpression StatementExpression
| TypedExpression DataType Expression | TypedExpression DataType Expression
deriving(Show, Eq)

View File

@ -1,6 +1,6 @@
{ {
module Parser.JavaParser (parse) where module Parser.JavaParser (parse) where
--import AbsSyn import Ast
import Parser.Lexer import Parser.Lexer
} }
@ -14,10 +14,10 @@ import Parser.Lexer
CASE { CASE } CASE { CASE }
CHAR { CHAR } CHAR { CHAR }
CLASS { CLASS} CLASS { CLASS}
IDENTIFIER { IDENTIFIER $$} IDENTIFIER { IDENTIFIER $$ }
INTLITERAL { INTLITERAL $$} INTLITERAL { INTEGERLITERAL $$}
DOT { DOT } DOT { DOT }
MOD { MOD } MOD { MODULO }
TIMESEQUAL { TIMESEQUAL } TIMESEQUAL { TIMESEQUAL }
GREATEREQUAL { GREATEREQUAL } GREATEREQUAL { GREATEREQUAL }
WHILE { WHILE } WHILE { WHILE }
@ -29,30 +29,29 @@ import Parser.Lexer
THIS { THIS } THIS { THIS }
STATIC { STATIC } STATIC { STATIC }
PROTECTED { PROTECTED } PROTECTED { PROTECTED }
TILDE { TILDE } TILDE { BITWISENOT }
MUL { MUL } MUL { TIMES }
MINUS { MINUS } MINUS { MINUS }
EXCLMARK { EXCLMARK } EXCLMARK { NOT }
IF { IF } IF { IF }
ELSE { ELSE } ELSE { ELSE }
DIVIDEEQUAL { DIVIDEEQUAL } DIVIDEEQUAL { DIVEQUAL }
NEW { NEW } NEW { NEW }
LBRACKET { LBRACKET } LBRACKET { LBRACKET }
JNULL { JNULL } JNULL { NULLLITERAL }
BOOLLITERAL { BOOLLITERAL } BOOLLITERAL { BOOLLITERAL $$ }
DIV { DIV } DIV { DIV }
LOGICALOR { LOGICALOR } LOGICALOR { OR }
NOTEQUAL { NOTEQUAL } NOTEQUAL { NOTEQUAL }
INSTANCEOF { INSTANCEOF } INSTANCEOF { INSTANCEOF }
ANDEQUAL { ANDEQUAL } ANDEQUAL { ANDEQUAL }
ASSIGN { ASSIGN } ASSIGN { ASSIGN }
DECREMENT { DECREMENT } DECREMENT { DECREMENT }
STRINGLITERAL { STRINGLITERAL } CHARLITERAL { CHARLITERAL $$ }
CHARLITERAL { CHARLITERAL }
AND { AND } AND { AND }
XOREQUAL { XOREQUAL } XOREQUAL { XOREQUAL }
RETURN { RETURN } RETURN { RETURN }
QUESMARK { QUESMARK } QUESMARK { QUESTIONMARK }
SHIFTLEFTEQUAL { SHIFTLEFTEQUAL } SHIFTLEFTEQUAL { SHIFTLEFTEQUAL }
RBRACKET { RBRACKET } RBRACKET { RBRACKET }
COMMA { COMMA } COMMA { COMMA }
@ -68,7 +67,7 @@ import Parser.Lexer
INT { INT } INT { INT }
ABSTRACT { ABSTRACT } ABSTRACT { ABSTRACT }
SEMICOLON { SEMICOLON } SEMICOLON { SEMICOLON }
SIGNEDSHIFTRIGHTEQUAL { SIGNEDSHIFTRIGHTEQUAL } SIGNEDSHIFTRIGHTEQUAL { SHIFTRIGHTEQUAL }
UNSIGNEDSHIFTRIGHTEQUAL { UNSIGNEDSHIFTRIGHTEQUAL } UNSIGNEDSHIFTRIGHTEQUAL { UNSIGNEDSHIFTRIGHTEQUAL }
PLUSEQUAL { PLUSEQUAL } PLUSEQUAL { PLUSEQUAL }
OREQUAL { OREQUAL } OREQUAL { OREQUAL }
@ -76,138 +75,146 @@ import Parser.Lexer
LESS { LESS } LESS { LESS }
%% %%
compilationunit : typedeclarations { } compilationunit : typedeclarations { $1 }
typedeclarations : typedeclaration { } typedeclarations : typedeclaration { [$1] }
| typedeclarations typedeclaration { } | typedeclarations typedeclaration { $1 ++ [$2] }
name : qualifiedname { } name : qualifiedname { }
| simplename { } | simplename { }
typedeclaration : classdeclaration { } typedeclaration : classdeclaration { $1 }
qualifiedname : name DOT IDENTIFIER { } qualifiedname : name DOT IDENTIFIER { }
simplename : IDENTIFIER { } simplename : IDENTIFIER { }
classdeclaration : CLASS IDENTIFIER classbody { } classdeclaration : CLASS IDENTIFIER classbody { case $3 of (methods, fields) -> Class $2 methods fields }
| modifiers CLASS IDENTIFIER classbody { } -- | modifiers CLASS IDENTIFIER classbody { case $4 of (methods, fields) -> Class $3 methods fields }
classbody : LBRACKET RBRACKET { ([], []) } classbody : LBRACKET RBRACKET { ([], []) }
| LBRACKET classbodydeclarations RBRACKET { } | LBRACKET classbodydeclarations RBRACKET { $2 }
modifiers : modifier { } modifiers : modifier { }
| modifiers modifier { } | modifiers modifier { }
classbodydeclarations : classbodydeclaration { } classbodydeclarations : classbodydeclaration {
| classbodydeclarations classbodydeclaration{ } case $1 of
MethodDecl method -> ([method], [])
FieldDecls fields -> ([], fields)
}
-- | classbodydeclarations classbodydeclaration {
-- case ($1, $2) of
-- ((methods, fields), MethodDecl method) -> ((methods ++ [method]), fields)
-- ((methods, fields), FieldDecl field) -> (methods, (fields ++ [field]))
-- }
modifier : PUBLIC { } modifier : PUBLIC { }
| PROTECTED { } | PROTECTED { }
| PRIVATE { } | PRIVATE { }
| STATIC { } | STATIC { }
| ABSTRACT { } | ABSTRACT { }
classtype : classorinterfacetype{ } classtype : classorinterfacetype{ }
classbodydeclaration : classmemberdeclaration { } classbodydeclaration : classmemberdeclaration { $1 }
| constructordeclaration { } -- | constructordeclaration { FieldDecl $ VariableDeclaration "int" "a" Nothing } -- TODO
classorinterfacetype : name{ } classorinterfacetype : name{ }
classmemberdeclaration : fielddeclaration { } classmemberdeclaration : fielddeclaration { $1 }
| methoddeclaration { } -- | methoddeclaration { }
constructordeclaration : constructordeclarator constructorbody { } constructordeclaration : constructordeclarator constructorbody { }
| modifiers constructordeclarator constructorbody { } | modifiers constructordeclarator constructorbody { }
fielddeclaration : type variabledeclarators SEMICOLON { } fielddeclaration : type variabledeclarators SEMICOLON { FieldDecls $ map (convertDeclarator $1) $2 }
| modifiers type variabledeclarators SEMICOLON { } -- | modifiers type variabledeclarators SEMICOLON {}
methoddeclaration : methodheader methodbody { } methoddeclaration : methodheader methodbody { }
block : LBRACKET RBRACKET { } block : LBRACKET RBRACKET { }
| LBRACKET blockstatements RBRACKET { } | LBRACKET blockstatements RBRACKET { }
constructordeclarator : simplename LBRACE RBRACE { } constructordeclarator : simplename LBRACE RBRACE { }
| simplename LBRACE formalparameterlist RBRACE { } | simplename LBRACE formalparameterlist RBRACE { }
constructorbody : LBRACKET RBRACKET { } constructorbody : LBRACKET RBRACKET { }
| LBRACKET explicitconstructorinvocation RBRACKET { } | LBRACKET explicitconstructorinvocation RBRACKET { }
| LBRACKET blockstatements RBRACKET { } | LBRACKET blockstatements RBRACKET { }
| LBRACKET explicitconstructorinvocation blockstatements RBRACKET { } | LBRACKET explicitconstructorinvocation blockstatements RBRACKET { }
methodheader : type methoddeclarator { } methodheader : type methoddeclarator { }
| modifiers type methoddeclarator { } | modifiers type methoddeclarator { }
| VOID methoddeclarator { } | VOID methoddeclarator { }
| modifiers VOID methoddeclarator { } | modifiers VOID methoddeclarator { }
type : primitivetype { } type : primitivetype { $1 }
| referencetype { } -- | referencetype { }
variabledeclarators : variabledeclarator { } variabledeclarators : variabledeclarator { [$1] }
| variabledeclarators COMMA variabledeclarator { } -- | variabledeclarators COMMA variabledeclarator { $1 ++ [$3] }
methodbody : block { } methodbody : block { }
| SEMICOLON { } | SEMICOLON { }
blockstatements : blockstatement { } blockstatements : blockstatement { }
| blockstatements blockstatement { } | blockstatements blockstatement { }
formalparameterlist : formalparameter { } formalparameterlist : formalparameter { }
| formalparameterlist COMMA formalparameter{ } | formalparameterlist COMMA formalparameter{ }
explicitconstructorinvocation : THIS LBRACE RBRACE SEMICOLON { } explicitconstructorinvocation : THIS LBRACE RBRACE SEMICOLON { }
| THIS LBRACE argumentlist RBRACE SEMICOLON { } | THIS LBRACE argumentlist RBRACE SEMICOLON { }
classtypelist : classtype { } classtypelist : classtype { }
| classtypelist COMMA classtype { } | classtypelist COMMA classtype { }
methoddeclarator : IDENTIFIER LBRACE RBRACE { } methoddeclarator : IDENTIFIER LBRACE RBRACE { }
| IDENTIFIER LBRACE formalparameterlist RBRACE { } | IDENTIFIER LBRACE formalparameterlist RBRACE { }
primitivetype : BOOLEAN { } primitivetype : BOOLEAN { "boolean" }
| numerictype { } | numerictype { $1 }
referencetype : classorinterfacetype { } referencetype : classorinterfacetype { }
variabledeclarator : variabledeclaratorid { } variabledeclarator : variabledeclaratorid { Declarator $1 Nothing }
| variabledeclaratorid ASSIGN variableinitializer { } -- | variabledeclaratorid ASSIGN variableinitializer { Declarator $1 Nothing } -- TODO
blockstatement : localvariabledeclarationstatement { } blockstatement : localvariabledeclarationstatement { }
| statement { } | statement { }
formalparameter : type variabledeclaratorid { } formalparameter : type variabledeclaratorid { }
argumentlist : expression { } argumentlist : expression { }
| argumentlist COMMA expression { } | argumentlist COMMA expression { }
numerictype : integraltype { } numerictype : integraltype { $1 }
variabledeclaratorid : IDENTIFIER { } variabledeclaratorid : IDENTIFIER { $1 }
variableinitializer : expression { } variableinitializer : expression { }
localvariabledeclarationstatement : localvariabledeclaration SEMICOLON { } localvariabledeclarationstatement : localvariabledeclaration SEMICOLON { }
statement : statementwithouttrailingsubstatement{ } statement : statementwithouttrailingsubstatement{ }
| ifthenstatement { } | ifthenstatement { }
| ifthenelsestatement { } | ifthenelsestatement { }
| whilestatement { } | whilestatement { }
expression : assignmentexpression { } expression : assignmentexpression { }
integraltype : INT { } integraltype : INT { "int" }
| CHAR { } | CHAR { "char" }
localvariabledeclaration : type variabledeclarators { } localvariabledeclaration : type variabledeclarators { }
statementwithouttrailingsubstatement : block { } statementwithouttrailingsubstatement : block { }
| emptystatement { } | emptystatement { }
| expressionstatement { } | expressionstatement { }
| returnstatement { } | returnstatement { }
ifthenstatement : IF LBRACE expression RBRACE statement { } ifthenstatement : IF LBRACE expression RBRACE statement { }
@ -216,55 +223,55 @@ ifthenelsestatement : IF LBRACE expression RBRACE statementnoshortif ELSE state
whilestatement : WHILE LBRACE expression RBRACE statement { } whilestatement : WHILE LBRACE expression RBRACE statement { }
assignmentexpression : conditionalexpression { } assignmentexpression : conditionalexpression { }
| assignment{ } | assignment{ }
emptystatement : SEMICOLON { } emptystatement : SEMICOLON { }
expressionstatement : statementexpression SEMICOLON { } expressionstatement : statementexpression SEMICOLON { }
returnstatement : RETURN SEMICOLON { } returnstatement : RETURN SEMICOLON { }
| RETURN expression SEMICOLON { } | RETURN expression SEMICOLON { }
statementnoshortif : statementwithouttrailingsubstatement { } statementnoshortif : statementwithouttrailingsubstatement { }
| ifthenelsestatementnoshortif { } | ifthenelsestatementnoshortif { }
| whilestatementnoshortif { } | whilestatementnoshortif { }
conditionalexpression : conditionalorexpression { } conditionalexpression : conditionalorexpression { }
| conditionalorexpression QUESMARK expression COLON conditionalexpression { } | conditionalorexpression QUESMARK expression COLON conditionalexpression { }
assignment :lefthandside assignmentoperator assignmentexpression { } assignment :lefthandside assignmentoperator assignmentexpression { }
statementexpression : assignment { } statementexpression : assignment { }
| preincrementexpression { } | preincrementexpression { }
| predecrementexpression { } | predecrementexpression { }
| postincrementexpression { } | postincrementexpression { }
| postdecrementexpression { } | postdecrementexpression { }
| methodinvocation { } | methodinvocation { }
| classinstancecreationexpression { } | classinstancecreationexpression { }
ifthenelsestatementnoshortif :IF LBRACE expression RBRACE statementnoshortif ifthenelsestatementnoshortif :IF LBRACE expression RBRACE statementnoshortif
ELSE statementnoshortif { } ELSE statementnoshortif { }
whilestatementnoshortif : WHILE LBRACE expression RBRACE statementnoshortif { } whilestatementnoshortif : WHILE LBRACE expression RBRACE statementnoshortif { }
conditionalorexpression : conditionalandexpression { } conditionalorexpression : conditionalandexpression { }
| conditionalorexpression LOGICALOR conditionalandexpression{ } | conditionalorexpression LOGICALOR conditionalandexpression{ }
lefthandside : name { } lefthandside : name { }
assignmentoperator : ASSIGN{ } assignmentoperator : ASSIGN{ }
| TIMESEQUAL { } | TIMESEQUAL { }
| DIVIDEEQUAL { } | DIVIDEEQUAL { }
| MODULOEQUAL { } | MODULOEQUAL { }
| PLUSEQUAL { } | PLUSEQUAL { }
| MINUSEQUAL { } | MINUSEQUAL { }
| SHIFTLEFTEQUAL { } | SHIFTLEFTEQUAL { }
| SIGNEDSHIFTRIGHTEQUAL { } | SIGNEDSHIFTRIGHTEQUAL { }
| UNSIGNEDSHIFTRIGHTEQUAL { } | UNSIGNEDSHIFTRIGHTEQUAL { }
| ANDEQUAL { } | ANDEQUAL { }
| XOREQUAL { } | XOREQUAL { }
| OREQUAL{ } | OREQUAL{ }
preincrementexpression : INCREMENT unaryexpression { } preincrementexpression : INCREMENT unaryexpression { }
@ -275,9 +282,9 @@ postincrementexpression : postfixexpression INCREMENT { }
postdecrementexpression : postfixexpression DECREMENT { } postdecrementexpression : postfixexpression DECREMENT { }
methodinvocation : name LBRACE RBRACE { } methodinvocation : name LBRACE RBRACE { }
| name LBRACE argumentlist RBRACE { } | name LBRACE argumentlist RBRACE { }
| primary DOT IDENTIFIER LBRACE RBRACE { } | primary DOT IDENTIFIER LBRACE RBRACE { }
| primary DOT IDENTIFIER LBRACE argumentlist RBRACE { } | primary DOT IDENTIFIER LBRACE argumentlist RBRACE { }
classinstancecreationexpression : NEW classtype LBRACE RBRACE { } classinstancecreationexpression : NEW classtype LBRACE RBRACE { }
| NEW classtype LBRACE argumentlist RBRACE { } | NEW classtype LBRACE argumentlist RBRACE { }
@ -286,75 +293,85 @@ conditionalandexpression : inclusiveorexpression { }
fieldaccess : primary DOT IDENTIFIER { } fieldaccess : primary DOT IDENTIFIER { }
unaryexpression : preincrementexpression { } unaryexpression : preincrementexpression { }
| predecrementexpression { } | predecrementexpression { }
| PLUS unaryexpression { } | PLUS unaryexpression { }
| MINUS unaryexpression { } | MINUS unaryexpression { }
| unaryexpressionnotplusminus { } | unaryexpressionnotplusminus { }
postfixexpression : primary { } postfixexpression : primary { }
| name { } | name { }
| postincrementexpression { } | postincrementexpression { }
| postdecrementexpression{ } | postdecrementexpression{ }
primary : primarynonewarray { } primary : primarynonewarray { }
inclusiveorexpression : exclusiveorexpression { } inclusiveorexpression : exclusiveorexpression { }
| inclusiveorexpression OR exclusiveorexpression { } | inclusiveorexpression OR exclusiveorexpression { }
primarynonewarray : literal { } primarynonewarray : literal { }
| THIS { } | THIS { }
| LBRACE expression RBRACE { } | LBRACE expression RBRACE { }
| classinstancecreationexpression { } | classinstancecreationexpression { }
| fieldaccess { } | fieldaccess { }
| methodinvocation { } | methodinvocation { }
unaryexpressionnotplusminus : postfixexpression { } unaryexpressionnotplusminus : postfixexpression { }
| TILDE unaryexpression { } | TILDE unaryexpression { }
| EXCLMARK unaryexpression { } | EXCLMARK unaryexpression { }
| castexpression{ } | castexpression{ }
exclusiveorexpression : andexpression { } exclusiveorexpression : andexpression { }
| exclusiveorexpression XOR andexpression { } | exclusiveorexpression XOR andexpression { }
literal : INTLITERAL { } literal : INTLITERAL { }
| BOOLLITERAL { } | BOOLLITERAL { }
| CHARLITERAL { } | CHARLITERAL { }
| STRINGLITERAL { } | JNULL { }
| JNULL { }
castexpression : LBRACE primitivetype RBRACE unaryexpression { } castexpression : LBRACE primitivetype RBRACE unaryexpression { }
| LBRACE expression RBRACE unaryexpressionnotplusminus{ } | LBRACE expression RBRACE unaryexpressionnotplusminus{ }
andexpression : equalityexpression { } andexpression : equalityexpression { }
| andexpression AND equalityexpression { } | andexpression AND equalityexpression { }
equalityexpression : relationalexpression { } equalityexpression : relationalexpression { }
| equalityexpression EQUAL relationalexpression { } | equalityexpression EQUAL relationalexpression { }
| equalityexpression NOTEQUAL relationalexpression { } | equalityexpression NOTEQUAL relationalexpression { }
relationalexpression : shiftexpression { } relationalexpression : shiftexpression { }
| relationalexpression LESS shiftexpression { } | relationalexpression LESS shiftexpression { }
| relationalexpression GREATER shiftexpression { } | relationalexpression GREATER shiftexpression { }
| relationalexpression LESSEQUAL shiftexpression { } | relationalexpression LESSEQUAL shiftexpression { }
| relationalexpression GREATEREQUAL shiftexpression { } | relationalexpression GREATEREQUAL shiftexpression { }
| relationalexpression INSTANCEOF referencetype { } | relationalexpression INSTANCEOF referencetype { }
shiftexpression : additiveexpression { } shiftexpression : additiveexpression { }
additiveexpression : multiplicativeexpression { } additiveexpression : multiplicativeexpression { }
| additiveexpression PLUS multiplicativeexpression { } | additiveexpression PLUS multiplicativeexpression { }
| additiveexpression MINUS multiplicativeexpression { } | additiveexpression MINUS multiplicativeexpression { }
multiplicativeexpression : unaryexpression { } multiplicativeexpression : unaryexpression { }
| multiplicativeexpression MUL unaryexpression { } | multiplicativeexpression MUL unaryexpression { }
| multiplicativeexpression DIV unaryexpression { } | multiplicativeexpression DIV unaryexpression { }
| multiplicativeexpression MOD unaryexpression { } | multiplicativeexpression MOD unaryexpression { }
{ {
data MethodOrFieldDeclaration = MethodDecl MethodDeclaration
| FieldDecls [VariableDeclaration]
data Declarator = Declarator Identifier (Maybe Expression)
-- convertDeclaratorList :: [DataType] -> MethodOrFieldDeclaration
-- convertDeclaratorList = FieldDecls $ map
convertDeclarator :: DataType -> Declarator -> VariableDeclaration
convertDeclarator dataType (Declarator id assigment) = VariableDeclaration dataType id assigment
parseError :: [Token] -> a parseError :: [Token] -> a
parseError _ = error "Parse error" parseError msg = error ("Parse error: " ++ show msg)
} }

View File

@ -1,5 +1,6 @@
{ {
module Parser.Lexer(Token(..), alexScanTokens) where module Parser.Lexer(Token(..), alexScanTokens) where
import Text.Read
} }
%wrapper "basic" %wrapper "basic"
@ -14,12 +15,214 @@ tokens :-
$white ; $white ;
"/*"(.|\n)*"*/" ; "/*"(.|\n)*"*/" ;
"//".* ; "//".* ;
$JavaLetter$JavaLetterOrDigit* { \s -> Identifier s } -- keywords
"abstract" { \_ -> ABSTRACT }
"assert" { \_ -> BOOLEAN }
"boolean" { \_ -> BOOLEAN}
"break" { \_ -> BREAK}
"byte" { \_ -> BYTE}
"case" { \_ -> CASE}
"catch" { \_ -> CATCH}
"char" { \_ -> CHAR}
"class" { \_ -> CLASS}
"const" { \_ -> CONST}
"continue" { \_ -> CONTINUE}
"default" { \_ -> DEFAULT}
"do" { \_ -> DO}
"double" { \_ -> DOUBLE}
("else"|"ifn't") { \_ -> ELSE}
"enum" { \_ -> ENUM}
"extends" { \_ -> EXTENDS}
"final" { \_ -> FINAL}
"finally" { \_ -> FINALLY}
"float" { \_ -> FLOAT}
"for" { \_ -> FOR}
"if" { \_ -> IF}
"goto" { \_ -> GOTO}
"implements" { \_ -> IMPLEMENTS}
"import" { \_ -> IMPORT}
"instanceof" { \_ -> INSTANCEOF}
"int" { \_ -> INT}
"long" { \_ -> LONG}
"native" { \_ -> NATIVE}
"new" { \_ -> NEW}
"package" { \_ -> PACKAGE}
"private" { \_ -> PRIVATE}
"protected" { \_ -> PROTECTED}
"public" { \_ -> PUBLIC}
"return" { \_ -> RETURN}
"short" { \_ -> SHORT}
"static" { \_ -> STATIC}
"strictfp" { \_ -> STRICTFP}
"super" { \_ -> SUPER}
"switch" { \_ -> SWITCH}
"synchronized" { \_ -> SYNCHRONIZED}
"this" { \_ -> THIS}
"throw" { \_ -> THROW}
"throws" { \_ -> THROWS}
"transient" { \_ -> TRANSIENT}
"try" { \_ -> TRY}
"void" { \_ -> VOID}
"volatile" { \_ -> VOLATILE}
"while" { \_ -> WHILE}
-- Literals
"true" { \_ -> BOOLLITERAL True }
"false" { \_ -> BOOLLITERAL False }
"null" { \_ -> NULLLITERAL }
-- end keywords
$JavaLetter$JavaLetterOrDigit* { \s -> IDENTIFIER s }
-- Literals
[1-9]([0-9\_]*[0-9])* { \s -> case readMaybe $ filter ((/=) '_') s of Just a -> INTEGERLITERAL a; Nothing -> error ("failed to parse INTLITERAL " ++ s) }
"'"."'" { \s -> case (s) of _ : c : _ -> CHARLITERAL c; _ -> error ("failed to parse CHARLITERAL " ++ s) }
-- separators
"(" { \_ -> LBRACE }
")" { \_ -> RBRACE }
"{" { \_ -> LBRACKET }
"}" { \_ -> RBRACKET }
";" { \_ -> SEMICOLON }
"," { \_ -> COMMA}
"." { \_ -> DOT }
-- operators
"=" { \_ -> ASSIGN }
"==" { \_ -> EQUAL }
"+" { \_ -> PLUS }
"+=" { \_ -> PLUSEQUAL }
">" { \_ -> GREATER }
">=" { \_ -> GREATEREQUAL }
"-" { \_ -> MINUS }
"-=" { \_ -> MINUSEQUAL }
"<" { \_ -> LESS }
"<=" { \_ -> LESSEQUAL }
"*" { \_ -> TIMES }
"*=" { \_ -> TIMESEQUAL }
"!" { \_ -> NOT }
"!=" { \_ -> NOTEQUAL }
"/" { \_ -> DIV }
"/=" { \_ -> DIVEQUAL }
"~" { \_ -> BITWISENOT }
"&&" { \_ -> AND }
"&" { \_ -> BITWISEAND }
"&=" { \_ -> ANDEQUAL }
"?" { \_ -> QUESTIONMARK }
"||" { \_ -> OR }
"|" { \_ -> BITWISEOR }
"|=" { \_ -> OREQUAL }
":" { \_ -> COLON }
"++" { \_ -> INCREMENT }
"^" { \_ -> XOR }
"^=" { \_ -> XOREQUAL }
"--" { \_ -> DECREMENT }
"%" { \_ -> MODULO }
"%=" { \_ -> MODULOEQUAL }
"<<" { \_ -> SHIFTLEFT }
"<<=" { \_ -> SHIFTLEFTEQUAL }
">>" { \_ -> SHIFTRIGHT }
">>=" { \_ -> SHIFTRIGHTEQUAL }
">>>" { \_ -> UNSIGNEDSHIFTRIGHT }
">>>=" { \_ -> UNSIGNEDSHIFTRIGHTEQUAL }
{ {
data Token data Token
= Identifier String = ABSTRACT
| ASSERT
| BOOLEAN
| BREAK
| BYTE
| CASE
| CATCH
| CHAR
| CLASS
| CONST
| CONTINUE
| DEFAULT
| DO
| DOUBLE
| ELSE
| ENUM
| EXTENDS
| FINAL
| FINALLY
| FLOAT
| FOR
| IF
| GOTO
| IMPLEMENTS
| IMPORT
| INSTANCEOF
| INT
| INTERFACE
| LONG
| NATIVE
| NEW
| PACKAGE
| PRIVATE
| PROTECTED
| PUBLIC
| RETURN
| SHORT
| STATIC
| STRICTFP
| SUPER
| SWITCH
| SYNCHRONIZED
| THIS
| THROW
| THROWS
| TRANSIENT
| TRY
| VOID
| VOLATILE
| WHILE
| IDENTIFIER String
| INTEGERLITERAL Int
| CHARLITERAL Char
| BOOLLITERAL Bool
| NULLLITERAL
| LBRACE
| RBRACE
| LBRACKET
| RBRACKET
| SEMICOLON
| COMMA
| DOT
| ASSIGN
| EQUAL
| PLUS
| PLUSEQUAL
| GREATER
| GREATEREQUAL
| MINUS
| MINUSEQUAL
| LESS
| LESSEQUAL
| TIMES
| TIMESEQUAL
| NOT
| NOTEQUAL
| DIV
| DIVEQUAL
| BITWISENOT
| AND
| BITWISEAND
| ANDEQUAL
| QUESTIONMARK
| OR
| BITWISEOR
| OREQUAL
| COLON
| INCREMENT
| XOR
| XOREQUAL
| DECREMENT
| MODULO
| MODULOEQUAL
| SHIFTLEFT
| SHIFTLEFTEQUAL
| SHIFTRIGHT
| SHIFTRIGHTEQUAL
| UNSIGNEDSHIFTRIGHT
| UNSIGNEDSHIFTRIGHTEQUAL
deriving(Eq,Show) deriving(Eq,Show)
} }