Skip to content

Commit

Permalink
[Fix] tests
Browse files Browse the repository at this point in the history
  • Loading branch information
nydragon committed Mar 8, 2023
1 parent f02ffe9 commit c22465d
Show file tree
Hide file tree
Showing 4 changed files with 25 additions and 17 deletions.
1 change: 1 addition & 0 deletions GLaDOS2023.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -123,6 +123,7 @@ test-suite unit-tests
CompilationLib.Parser.CptTests,
CompilationLib.Parser.AstTests,
CompilationLib.Parser.InfixTests,
CompilationLib.Compilation.CompilationTests,
ExecLib.Exec.Infer,
ExecLib.Exec.Instructions,
ExecLib.Exec.Utils,
Expand Down
4 changes: 3 additions & 1 deletion tests/unit-tests/CompilationLib.hs
Original file line number Diff line number Diff line change
Expand Up @@ -8,12 +8,14 @@ import CompilationLib.Parser.ArgsTests ( argsSuite )
import CompilationLib.Parser.AstTests ( astSuite )
import CompilationLib.Parser.TokenTests ( tokenSuite )
import CompilationLib.Parser.InfixTests ( infixSuite )
import CompilationLib.Compilation.CompilationTests (testCompileConditional)

compilationLibSuite :: TestTree
compilationLibSuite = testGroup "Parsing Testsuite" [
argsSuite,
tokenSuite,
cptSuite,
astSuite,
infixSuite
infixSuite,
testCompileConditional
]
21 changes: 21 additions & 0 deletions tests/unit-tests/CompilationLib/Compilation/CompilationTests.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,21 @@
module CompilationLib.Compilation.CompilationTests where

import Test.Tasty (TestTree, testGroup)
import Test.Tasty.HUnit (testCase, (@=?), assertEqual)
import qualified Parsing.Ast as Ast
import Compilation.RetVal (RetVal(RetVal))
import Parsing.Ast (Expr(Num))
import qualified Exec.InferType as Type
import qualified Instruction as Type
import Compilation.Compile (compileConditional)
import Instruction (Instruction(Push))

testCompileConditional :: TestTree
testCompileConditional = testGroup "compileConditional"
[ testCase "simple conditional" $
let ast = Ast.Call "if" [ Ast.Boolean True, Ast.Num 1, Ast.Num 2 ]
reg = (["foo"], [])
RetVal instrs blocks reg' = compileConditional ast reg
in do
assertEqual "instructions" [Type.Conditional [Push "#t"] [Push "1"] [Push "2"]] instrs
]

This file was deleted.

0 comments on commit c22465d

Please sign in to comment.