1
1
mirror of https://github.com/anoma/juvix.git synced 2025-01-05 22:46:08 +03:00

JuvixTree negative evaluation tests (#2601)

* Adds negative tests for the JuvixTree evaluator
* Depends on #2600 
* Depends on #2599 
* Depends on #2598 
* Depends on #2597 
* Depends on #2596 
* Depends on #2595 
* Depends on #2594 
* Depends on #2590
This commit is contained in:
Łukasz Czajka 2024-02-01 13:58:38 +01:00 committed by GitHub
parent b433eb48cb
commit 7b0a11d570
No known key found for this signature in database
GPG Key ID: B5690EEEBB952194
12 changed files with 165 additions and 3 deletions

View File

@ -66,8 +66,12 @@ hEval hout tab = eval' [] mempty
IntAdd -> goIntBinop (+) arg1 arg2
IntSub -> goIntBinop (-) arg1 arg2
IntMul -> goIntBinop (*) arg1 arg2
IntDiv -> goIntBinop quot arg1 arg2
IntMod -> goIntBinop rem arg1 arg2
IntDiv
| arg2 == ValInteger 0 -> evalError "division by zero"
| otherwise -> goIntBinop quot arg1 arg2
IntMod
| arg2 == ValInteger 0 -> evalError "division by zero"
| otherwise -> goIntBinop rem arg1 arg2
IntLe -> goIntCmpBinop (<=) arg1 arg2
IntLt -> goIntCmpBinop (<) arg1 arg2
ValEq

View File

@ -1,7 +1,8 @@
module Tree.Eval where
import Base
import Tree.Eval.Negative qualified as N
import Tree.Eval.Positive qualified as P
allTests :: TestTree
allTests = testGroup "JuvixTree evaluation" [P.allTests]
allTests = testGroup "JuvixTree evaluation" [P.allTests, N.allTests]

View File

@ -73,3 +73,25 @@ doEval ::
FunctionInfo ->
IO (Either TreeError Value)
doEval hout tab funInfo = catchEvalErrorIO (hEvalIO stdin hout tab funInfo)
treeEvalErrorAssertion :: Path Abs File -> (String -> IO ()) -> Assertion
treeEvalErrorAssertion mainFile step = do
step "Parse"
s <- readFile (toFilePath mainFile)
case runParser (toFilePath mainFile) s of
Left err -> assertFailure (show (pretty err))
Right tab ->
case tab ^. infoMainFunction of
Just sym -> do
withTempDir'
( \dirPath -> do
let outputFile = dirPath <//> $(mkRelFile "out.out")
hout <- openFile (toFilePath outputFile) WriteMode
step "Evaluate"
r' <- doEval hout tab (lookupFunInfo tab sym)
hClose hout
case r' of
Left _ -> assertBool "" True
Right _ -> assertFailure "no error"
)
Nothing -> assertFailure "no main function"

View File

@ -0,0 +1,65 @@
module Tree.Eval.Negative where
import Base
import Tree.Eval.Base
data NegTest = NegTest
{ _name :: String,
_relDir :: Path Rel Dir,
_file :: Path Rel File
}
root :: Path Abs Dir
root = relToProject $(mkRelDir "tests/Tree/negative")
testDescr :: NegTest -> TestDescr
testDescr NegTest {..} =
let tRoot = root <//> _relDir
file' = tRoot <//> _file
in TestDescr
{ _testName = _name,
_testRoot = tRoot,
_testAssertion = Steps $ treeEvalErrorAssertion file'
}
allTests :: TestTree
allTests =
testGroup
"JuvixTree negative tests"
(map (mkTest . testDescr) tests)
tests :: [NegTest]
tests =
[ NegTest
"Test001: Division by zero"
$(mkRelDir ".")
$(mkRelFile "test001.jvt"),
NegTest
"Test002: Arithmetic operations on non-numbers"
$(mkRelDir ".")
$(mkRelFile "test002.jvt"),
NegTest
"Test003: Case on non-data"
$(mkRelDir ".")
$(mkRelFile "test003.jvt"),
NegTest
"Test004: If on non-boolean"
$(mkRelDir ".")
$(mkRelFile "test004.jvt"),
NegTest
"Test005: No matching case branch"
$(mkRelDir ".")
$(mkRelFile "test005.jvt"),
NegTest
"Test006: Invalid closure call"
$(mkRelDir ".")
$(mkRelFile "test006.jvt"),
NegTest
"Test007: Call: wrong number of arguments"
$(mkRelDir ".")
$(mkRelFile "test007.jvt"),
NegTest
"Test008: Closure call: wrong number of arguments"
$(mkRelDir ".")
$(mkRelFile "test008.jvt")
]

View File

@ -0,0 +1,9 @@
-- division by zero
function f(x : integer) : integer {
div(2, x)
}
function main() : * {
call[f](0)
}

View File

@ -0,0 +1,5 @@
-- arithmetic operations on non-numbers
function main() : * {
add(2, calloc[main]())
}

View File

@ -0,0 +1,13 @@
-- case on non-data
type list {
nil : list;
cons : * -> list -> list;
}
function main() : * {
case[list](3) {
nil: 0
cons: 1
}
}

View File

@ -0,0 +1,8 @@
-- if on non-boolean
function main() : * {
br(3) {
true: 0
false: 1
}
}

View File

@ -0,0 +1,12 @@
-- no matching case branch
type list {
nil : list;
cons : * -> list -> list;
}
function main() : * {
case[list](alloc[nil]()) {
cons: 1
}
}

View File

@ -0,0 +1,5 @@
-- invalid closure call
function main() : * {
call(2, 1)
}

View File

@ -0,0 +1,9 @@
-- call: wrong number of arguments
function f(x : *) : * {
x
}
function main() : * {
call[f](10, 11)
}

View File

@ -0,0 +1,9 @@
-- closure call: wrong number of arguments
function f(x : *) : * {
x
}
function main() : * {
call(calloc[f](), 10, 11)
}