aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorJuan J. Martinez <jjm@usebox.net>2022-08-15 21:57:48 +0100
committerJuan J. Martinez <jjm@usebox.net>2022-08-15 21:57:48 +0100
commitb167fe5295b8e54ed962b59118ce71d3e0cc73fd (patch)
tree6e49906ac59bf63afc35e96ab54c04eb562f5e3c
parentde2acb78940df97bd337bb3e8e366c75739390bc (diff)
downloadmicro-lang-hs-b167fe5295b8e54ed962b59118ce71d3e0cc73fd.tar.gz
micro-lang-hs-b167fe5295b8e54ed962b59118ce71d3e0cc73fd.zip
Some tests for the AST
-rw-r--r--micro2.cabal1
-rw-r--r--test/Language.hs51
2 files changed, 51 insertions, 1 deletions
diff --git a/micro2.cabal b/micro2.cabal
index 30bec21..2eadeca 100644
--- a/micro2.cabal
+++ b/micro2.cabal
@@ -55,6 +55,7 @@ test-suite tests
Language
build-depends:
base ^>= 4.16.1.0
+ , parsec ^>= 3.1.15.1
, HUnit
, micro2
hs-source-dirs: test
diff --git a/test/Language.hs b/test/Language.hs
index 9479380..ea387d8 100644
--- a/test/Language.hs
+++ b/test/Language.hs
@@ -1,11 +1,60 @@
module Language where
+import qualified Ast as A
import Compiler
import Lexer (scan)
import Parser (parse)
import Test.HUnit
+import Text.Parsec (runParser)
+import Text.Parsec.Pos (newPos)
+
+assertAst :: String -> String -> [A.Expr] -> Assertion
+assertAst tcase input expected = do
+ r <- return $ runParser (scan parse) () "test" input
+ case r of
+ Left e -> assertFailure $ show e
+ Right ast -> assertEqual tcase ast expected
testCase = TestCase $ do
- assertEqual "placeholder" True True
+ assertAst "parse module" "module main" [A.Module "main" $ newPos "test" 1 1]
+ assertAst
+ "parse a function"
+ "module main\n\
+ \def fn() { }"
+ [ A.Module "main" $ newPos "test" 1 1,
+ A.Func "fn" [] Nothing [] False False $ newPos "test" 2 1
+ ]
+ assertAst
+ "parse a function with parameters"
+ "module main\n\
+ \def fn(a: u8) { }"
+ [ A.Module "main" $ newPos "test" 1 1,
+ A.Func "fn" [("a", A.Type "u8", newPos "test" 2 8)] Nothing [] False False $ newPos "test" 2 1
+ ]
+ assertAst
+ "parse a function with return value"
+ "module main\n\
+ \def fn(): u8 { }"
+ [ A.Module "main" $ newPos "test" 1 1,
+ A.Func "fn" [] (Just $ A.Type "u8") [] False False $ newPos "test" 2 1
+ ]
+ assertAst
+ "parse a function call"
+ "module main\n\
+ \def fn() { }\n\
+ \fn();"
+ [ A.Module "main" $ newPos "test" 1 1,
+ A.Func "fn" [] Nothing [] False False $ newPos "test" 2 1,
+ A.Call (A.Var "fn" $ newPos "test" 3 1) [] $ newPos "test" 3 1
+ ]
+ assertAst
+ "parse a function call with arguments"
+ "module main\n\
+ \def fn(a: u8) { }\n\
+ \fn(10);"
+ [ A.Module "main" $ newPos "test" 1 1,
+ A.Func "fn" [("a", A.Type "u8", newPos "test" 2 8)] Nothing [] False False $ newPos "test" 2 1,
+ A.Call (A.Var "fn" $ newPos "test" 3 1) [A.Num 10 $ newPos "test" 3 4] $ newPos "test" 3 1
+ ]
language = [testCase]