diff options
author | Juan J. Martinez <jjm@usebox.net> | 2022-08-16 23:10:06 +0100 |
---|---|---|
committer | Juan J. Martinez <jjm@usebox.net> | 2022-08-16 23:10:06 +0100 |
commit | 7b57942b3a10e51fdb7f78d276dc0187a22c3871 (patch) | |
tree | 8af77798f00353dcc77e85aa3e167f7aff9e0ba7 /test/Language.hs | |
parent | 55692e10192968ae7f040ceb9a8469b6ce2412c4 (diff) | |
download | micro-lang-hs-7b57942b3a10e51fdb7f78d276dc0187a22c3871.tar.gz micro-lang-hs-7b57942b3a10e51fdb7f78d276dc0187a22c3871.zip |
Test labels, test for errors WIP
Diffstat (limited to 'test/Language.hs')
-rw-r--r-- | test/Language.hs | 268 |
1 files changed, 152 insertions, 116 deletions
diff --git a/test/Language.hs b/test/Language.hs index c804035..7892c16 100644 --- a/test/Language.hs +++ b/test/Language.hs @@ -2,149 +2,185 @@ module Language where import qualified Ast as A import Compiler +import Control.Monad.State (evalState) +import qualified Error as E 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 +assertAst :: String -> [A.Expr] -> Assertion +assertAst input expected = do r <- return $ runParser (scan parse) () "test" input case r of Left e -> assertFailure $ show e - Right ast -> assertEqual tcase expected ast + Right ast -> assertEqual "" expected ast -testCase1 = TestCase $ assertAst "parse module" "module main" [A.Module "main" $ newPos "test" 1 1] +expectError :: String -> IO (Maybe E.Error) +expectError input = do + r <- return $ runParser (scan parse) () "test" input + case r of + Left e -> assertFailure $ show e + Right ast -> do + res <- return $ evalState (compileAll ast) startState + case res of + Left (e : _) -> return $ Just e + Right _ -> return $ Nothing + +testCase1 = + TestLabel "parse module" $ + TestCase $ + assertAst "module main" [A.Module "main" $ newPos "test" 1 1] testCase2 = - TestCase $ - 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 - ] + TestLabel + "parse a function" + $ TestCase $ + assertAst + "module main\n\ + \def fn() { }" + [ A.Module "main" $ newPos "test" 1 1, + A.Func "fn" [] Nothing [] False False $ newPos "test" 2 1 + ] testCase3 = - TestCase $ - 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 - ] + TestLabel + "parse a function with parameters" + $ TestCase $ + assertAst + "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 + ] testCase4 = - TestCase $ - assertAst - "parse a function with return value" - "module main\n\ - \def fn(): u8 {\n\ - \return 1; }" - [ A.Module "main" $ newPos "test" 1 1, - A.Func "fn" [] (Just $ A.Type "u8") [A.Return (Just $ A.Num 1 $ newPos "test" 3 8) $ newPos "test" 3 1] False False $ newPos "test" 2 1 - ] + TestLabel + "parse a function with return value" + $ TestCase $ + assertAst + "module main\n\ + \def fn(): u8 {\n\ + \return 1; }" + [ A.Module "main" $ newPos "test" 1 1, + A.Func "fn" [] (Just $ A.Type "u8") [A.Return (Just $ A.Num 1 $ newPos "test" 3 8) $ newPos "test" 3 1] False False $ newPos "test" 2 1 + ] testCase5 = - TestCase $ - 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 - ] + TestLabel + "parse a function call" + $ TestCase $ + assertAst + "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 + ] testCase6 = - TestCase $ - 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 - ] + TestLabel + "parse a function call with arguments" + $ TestCase $ + assertAst + "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 + ] testCase7 = - TestCase $ - assertAst - "parse empty return on a function" - "module main\n\ - \def fn() {\n\ - \return; }" - [ A.Module "main" $ newPos "test" 1 1, - A.Func "fn" [] Nothing [A.Return Nothing $ newPos "test" 3 1] False False $ newPos "test" 2 1 - ] + TestLabel + "parse empty return on a function" + $ TestCase $ + assertAst + "module main\n\ + \def fn() {\n\ + \return; }" + [ A.Module "main" $ newPos "test" 1 1, + A.Func "fn" [] Nothing [A.Return Nothing $ newPos "test" 3 1] False False $ newPos "test" 2 1 + ] testCase8 = - TestCase $ - assertAst - "parse a recursive function" - "module main\n\ - \def fn() {\n\ - \fn(); }" - [ A.Module "main" $ newPos "test" 1 1, - A.Func "fn" [] Nothing [A.Call (A.Var "fn" $ newPos "test" 3 1) [] $ newPos "test" 3 1] False False $ newPos "test" 2 1 - ] + TestLabel + "parse a recursive function" + $ TestCase $ + assertAst + "module main\n\ + \def fn() {\n\ + \fn(); }" + [ A.Module "main" $ newPos "test" 1 1, + A.Func "fn" [] Nothing [A.Call (A.Var "fn" $ newPos "test" 3 1) [] $ newPos "test" 3 1] False False $ newPos "test" 2 1 + ] testCase9 = - TestCase $ - assertAst - "parse a function with a function parameter" - "module main\n\ - \def fn1() { }\n\ - \def fn2(f: ()) {\n\ - \f(); }\n\ - \fn2(fn1);" - [ A.Module "main" $ newPos "test" 1 1, - A.Func "fn1" [] Nothing [] False False $ newPos "test" 2 1, - A.Func - "fn2" - [("f", A.FuncType [] Nothing, newPos "test" 3 9)] - Nothing - [ A.Call (A.Var "f" $ newPos "test" 4 1) [] $ newPos "test" 4 1 - ] - False - False - $ newPos "test" 3 1, - A.Call (A.Var "fn2" $ newPos "test" 5 1) [A.Var "fn1" $ newPos "test" 5 5] $ newPos "test" 5 1 - ] + TestLabel + "parse a function with a function parameter" + $ TestCase $ + assertAst + "module main\n\ + \def fn1() { }\n\ + \def fn2(f: ()) {\n\ + \f(); }\n\ + \fn2(fn1);" + [ A.Module "main" $ newPos "test" 1 1, + A.Func "fn1" [] Nothing [] False False $ newPos "test" 2 1, + A.Func + "fn2" + [("f", A.FuncType [] Nothing, newPos "test" 3 9)] + Nothing + [ A.Call (A.Var "f" $ newPos "test" 4 1) [] $ newPos "test" 4 1 + ] + False + False + $ newPos "test" 3 1, + A.Call (A.Var "fn2" $ newPos "test" 5 1) [A.Var "fn1" $ newPos "test" 5 5] $ newPos "test" 5 1 + ] testCase10 = - TestCase $ - assertAst - "parse a function with a function parameter (lambda)" - "module main\n\ - \def fn(f: ()) {\n\ - \f(); }\n\ - \fn(() { });" - [ A.Module "main" $ newPos "test" 1 1, - A.Func - "fn" - [("f", A.FuncType [] Nothing, newPos "test" 2 8)] - Nothing - [A.Call (A.Var "f" $ newPos "test" 3 1) [] $ newPos "test" 3 1] - False - False - $ newPos "test" 2 1, - A.Call (A.Var "fn" $ newPos "test" 4 1) [A.Func "lambda@4,4" [] Nothing [] True True $ newPos "test" 4 4] $ newPos "test" 4 1 - ] + TestLabel + "parse a function with a function parameter (lambda)" + $ TestCase $ + assertAst + "module main\n\ + \def fn(f: ()) {\n\ + \f(); }\n\ + \fn(() { });" + [ A.Module "main" $ newPos "test" 1 1, + A.Func + "fn" + [("f", A.FuncType [] Nothing, newPos "test" 2 8)] + Nothing + [A.Call (A.Var "f" $ newPos "test" 3 1) [] $ newPos "test" 3 1] + False + False + $ newPos "test" 2 1, + A.Call (A.Var "fn" $ newPos "test" 4 1) [A.Func "lambda@4,4" [] Nothing [] True True $ newPos "test" 4 4] $ newPos "test" 4 1 + ] testCase11 = - TestCase $ - assertAst - "parse a call to lambda" - "module main\n\ - \() { }();" - [ A.Module "main" $ newPos "test" 1 1, - A.Call (A.Func "lambda@2,1" [] Nothing [] True True $ newPos "test" 2 1) [] $ newPos "test" 2 1 - ] - -language = [testCase1, testCase2, testCase3, testCase4, testCase5, testCase6, testCase7, testCase8, testCase9, testCase10, testCase11] + TestLabel "parse a call to lambda" $ + TestCase $ + assertAst + "module main\n\ + \() { }();" + [ A.Module "main" $ newPos "test" 1 1, + A.Call (A.Func "lambda@2,1" [] Nothing [] True True $ newPos "test" 2 1) [] $ newPos "test" 2 1 + ] + +testCase12 = + TestLabel "invalid return value" $ + TestCase $ do + e <- + expectError + "module main\n\ + \def fn(): u8 { return; }" + case e of + Nothing -> assertFailure "expected error, didn't happen" + Just (E.TypeError _ _) -> return $ () + +language = [testCase1, testCase2, testCase3, testCase4, testCase5, testCase6, testCase7, testCase8, testCase9, testCase10, testCase11, testCase12] |