Parse all statements
This commit is contained in:
@ -2,14 +2,18 @@ module Language.Elna.ParserSpec
|
||||
( spec
|
||||
) where
|
||||
|
||||
import Test.Hspec (Spec, describe, it, pendingWith, xit)
|
||||
import Test.Hspec (Spec, describe, it)
|
||||
import Test.Hspec.Megaparsec (shouldParse, shouldSucceedOn, parseSatisfies)
|
||||
import Language.Elna.Parser (programP)
|
||||
import Text.Megaparsec (parse)
|
||||
import Language.Elna.AST
|
||||
( Declaration(..)
|
||||
, Expression(..)
|
||||
, Literal(..)
|
||||
, Statement(..)
|
||||
, Parameter(..)
|
||||
, Program(..)
|
||||
, VariableDeclaration(..)
|
||||
, TypeExpression(..)
|
||||
)
|
||||
|
||||
@ -54,5 +58,85 @@ spec =
|
||||
actual = parse programP "" given
|
||||
in actual `parseSatisfies` expected
|
||||
|
||||
it "parses procedure body statements" $
|
||||
pendingWith "Not implemented"
|
||||
it "parses negation" $
|
||||
let given = "proc main(x: integer) { var y: integer; y := -x; }"
|
||||
parameters = pure $ Parameter "x" (NamedType "integer") False
|
||||
variables = pure
|
||||
$ VariableDeclaration "y"
|
||||
$ NamedType "integer"
|
||||
body = pure
|
||||
$ AssignmentStatement (VariableExpression "y")
|
||||
$ NegationExpression
|
||||
$ VariableExpression "x"
|
||||
expected = Program
|
||||
[ProcedureDefinition "main" parameters variables body]
|
||||
actual = parse programP "" given
|
||||
in actual `shouldParse` expected
|
||||
|
||||
it "parses comparison with lower precedence than other binary operators" $
|
||||
let given = "proc main() { var x: boolean; x := 1 + 2 = 3 * 4; }"
|
||||
variables = pure
|
||||
$ VariableDeclaration "x"
|
||||
$ NamedType "boolean"
|
||||
lhs = SumExpression (LiteralExpression (IntegerLiteral 1))
|
||||
$ LiteralExpression (IntegerLiteral 2)
|
||||
rhs = ProductExpression (LiteralExpression (IntegerLiteral 3))
|
||||
$ LiteralExpression (IntegerLiteral 4)
|
||||
body = pure
|
||||
$ AssignmentStatement (VariableExpression "x")
|
||||
$ EqualExpression lhs rhs
|
||||
expected = Program
|
||||
[ProcedureDefinition "main" [] variables body]
|
||||
actual = parse programP "" given
|
||||
in actual `shouldParse` expected
|
||||
|
||||
it "parses hexadecimals" $
|
||||
let given = "proc main() { var x: integer; x := 0x10; }"
|
||||
variables = pure
|
||||
$ VariableDeclaration "x"
|
||||
$ NamedType "integer"
|
||||
body = pure
|
||||
$ AssignmentStatement (VariableExpression "x")
|
||||
$ LiteralExpression (HexadecimalLiteral 16)
|
||||
expected = Program
|
||||
[ProcedureDefinition "main" [] variables body]
|
||||
actual = parse programP "" given
|
||||
in actual `shouldParse` expected
|
||||
|
||||
it "parses procedure calls" $
|
||||
let given = "proc main() { f('c'); }"
|
||||
body = pure
|
||||
$ CallStatement "f" [LiteralExpression (CharacterLiteral 99)]
|
||||
expected = Program
|
||||
[ProcedureDefinition "main" [] [] body]
|
||||
actual = parse programP "" given
|
||||
in actual `shouldParse` expected
|
||||
|
||||
it "parses an if statement" $
|
||||
let given = "proc main() { if (true) ; }"
|
||||
body = pure
|
||||
$ IfStatement (LiteralExpression $ BooleanLiteral True) EmptyStatement Nothing
|
||||
expected = Program
|
||||
[ProcedureDefinition "main" [] [] body]
|
||||
actual = parse programP "" given
|
||||
in actual `shouldParse` expected
|
||||
|
||||
it "associates else with the nearst if statement" $
|
||||
let given = "proc main() { if (true) if (false) ; else ; }"
|
||||
if' = IfStatement (LiteralExpression $ BooleanLiteral False) EmptyStatement
|
||||
$ Just EmptyStatement
|
||||
body = pure
|
||||
$ IfStatement (LiteralExpression $ BooleanLiteral True) if' Nothing
|
||||
expected = Program
|
||||
[ProcedureDefinition "main" [] [] body]
|
||||
actual = parse programP "" given
|
||||
in actual `shouldParse` expected
|
||||
|
||||
it "parses a while statement" $
|
||||
let given = "proc main() { while (true) ; }"
|
||||
body = pure
|
||||
$ WhileStatement (LiteralExpression $ BooleanLiteral True) EmptyStatement
|
||||
expected = Program
|
||||
[ProcedureDefinition "main" [] [] body]
|
||||
actual = parse programP "" given
|
||||
in actual `shouldParse` expected
|
||||
|
Reference in New Issue
Block a user