parser implement class
This commit is contained in:
parent
fa2dc24aa0
commit
fa9cb761d5
@ -3,12 +3,19 @@ module TestParser(tests) where
|
|||||||
import Test.HUnit
|
import Test.HUnit
|
||||||
import Parser.Lexer
|
import Parser.Lexer
|
||||||
import Parser.JavaParser
|
import Parser.JavaParser
|
||||||
|
import Ast
|
||||||
|
|
||||||
|
|
||||||
testIntLiteral = TestCase $ assertEqual "IntLiteral 34" [IntLiteral 34] $ parse (INTLITERAL 34)
|
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]
|
||||||
|
|
||||||
|
|
||||||
testAnd = TestCase $ assertEqual "scan '&&'" [AND] $ alexScanTokens "&&"
|
|
||||||
|
|
||||||
tests = TestList [
|
tests = TestList [
|
||||||
testIntLiteral
|
testSingleEmptyClass,
|
||||||
|
testTwoEmptyClasses
|
||||||
]
|
]
|
@ -2,12 +2,12 @@ module Main where
|
|||||||
|
|
||||||
import Test.HUnit
|
import Test.HUnit
|
||||||
import TestLexer
|
import TestLexer
|
||||||
-- import TestParser
|
import TestParser
|
||||||
|
|
||||||
|
|
||||||
tests = TestList [
|
tests = TestList [
|
||||||
TestLabel "TestLexer" TestLexer.tests
|
TestLabel "TestLexer" TestLexer.tests,
|
||||||
-- TestLabel "TestParser" TestParser.tests
|
TestLabel "TestParser" TestParser.tests
|
||||||
]
|
]
|
||||||
|
|
||||||
main = do runTestTTAndExit Main.tests
|
main = do runTestTTAndExit Main.tests
|
@ -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)
|
||||||
|
|
@ -14,7 +14,7 @@ import Parser.Lexer
|
|||||||
CASE { CASE }
|
CASE { CASE }
|
||||||
CHAR { CHAR }
|
CHAR { CHAR }
|
||||||
CLASS { CLASS}
|
CLASS { CLASS}
|
||||||
IDENTIFIER { IDENTIFIER $$}
|
IDENTIFIER { IDENTIFIER $$ }
|
||||||
INTLITERAL { INTEGERLITERAL $$}
|
INTLITERAL { INTEGERLITERAL $$}
|
||||||
DOT { DOT }
|
DOT { DOT }
|
||||||
MOD { MODULO }
|
MOD { MODULO }
|
||||||
@ -75,25 +75,25 @@ 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, attributes) -> Class $2 methods attributes }
|
||||||
| modifiers CLASS IDENTIFIER classbody { }
|
| modifiers CLASS IDENTIFIER classbody { case $4 of (methods, attributes) -> Class $3 methods attributes }
|
||||||
|
|
||||||
classbody : LBRACKET RBRACKET { ([], []) }
|
classbody : LBRACKET RBRACKET { ([], []) }
|
||||||
| LBRACKET classbodydeclarations RBRACKET { }
|
| LBRACKET classbodydeclarations RBRACKET { ([], []) }
|
||||||
|
|
||||||
modifiers : modifier { }
|
modifiers : modifier { }
|
||||||
| modifiers modifier { }
|
| modifiers modifier { }
|
||||||
|
Loading…
Reference in New Issue
Block a user