Skip to content

Commit

Permalink
Add anoma compile negative test for strings
Browse files Browse the repository at this point in the history
We can remove the hack serialization of the output in the Anoma compile
positive tests. We were doing this to cover the string check
  • Loading branch information
paulcadman committed Mar 19, 2024
1 parent 64a4d09 commit 5afcae5
Show file tree
Hide file tree
Showing 5 changed files with 55 additions and 11 deletions.
3 changes: 0 additions & 3 deletions app/Commands/Dev/Nockma/Eval.hs
Original file line number Diff line number Diff line change
Expand Up @@ -26,6 +26,3 @@ runCommand opts = do
where
file :: AppPath File
file = opts ^. nockmaEvalFile

--- run-anoma --env ENV_FILE --profile INPUT_FILE
---
3 changes: 2 additions & 1 deletion test/Anoma/Compilation.hs
Original file line number Diff line number Diff line change
@@ -1,7 +1,8 @@
module Anoma.Compilation where

import Anoma.Compilation.Negative qualified as N
import Anoma.Compilation.Positive qualified as P
import Base

allTests :: TestTree
allTests = testGroup "Compilation to Anoma" [P.allTests]
allTests = testGroup "Compilation to Anoma" [P.allTests, N.allTests]
47 changes: 47 additions & 0 deletions test/Anoma/Compilation/Negative.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,47 @@
module Anoma.Compilation.Negative where

import Base
import Juvix.Compiler.Backend (Target (TargetAnoma))
import Juvix.Compiler.Core.Error
import Juvix.Prelude qualified as Prelude

root :: Prelude.Path Abs Dir
root = relToProject $(mkRelDir "tests/Anoma/Compilation/negative")

type CheckError = JuvixError -> IO ()

mkAnomaNegativeTest :: Text -> Prelude.Path Rel Dir -> Prelude.Path Rel File -> CheckError -> TestTree
mkAnomaNegativeTest testName' relRoot mainFile testCheck =
testCase (unpack testName') mkTestIO
where
mkTestIO :: IO ()
mkTestIO = do
merr <- withRootCopy compileMain
case merr of
Nothing -> assertFailure "expected compilation to fail"
Just err -> testCheck err

withRootCopy :: (Prelude.Path Abs Dir -> IO a) -> IO a
withRootCopy action = withSystemTempDir "test" $ \tmpRootDir -> do
copyDirRecur root tmpRootDir
action tmpRootDir

compileMain :: Prelude.Path Abs Dir -> IO (Maybe JuvixError)
compileMain rootCopyDir = do
let testRootDir = rootCopyDir <//> relRoot
entryPoint <-
set entryPointTarget TargetAnoma
<$> testDefaultEntryPointIO testRootDir (testRootDir <//> mainFile)
either Just (const Nothing) <$> testRunIOEither entryPoint upToAnoma

checkCoreError :: CheckError
checkCoreError e =
unless
(isJust (fromJuvixError @CoreError e))
(assertFailure ("Expected core error got: " <> unpack (renderTextDefault e)))

allTests :: TestTree
allTests =
testGroup
"Anoma negative tests"
[mkAnomaNegativeTest "Use of Strings" $(mkRelDir ".") $(mkRelFile "String.juvix") checkCoreError]
8 changes: 1 addition & 7 deletions test/Anoma/Compilation/Positive.hs
Original file line number Diff line number Diff line change
Expand Up @@ -5,7 +5,6 @@ import Juvix.Compiler.Backend (Target (TargetAnoma))
import Juvix.Compiler.Nockma.Anoma
import Juvix.Compiler.Nockma.Evaluator
import Juvix.Compiler.Nockma.Language
import Juvix.Compiler.Nockma.Pretty
import Juvix.Compiler.Nockma.Translation.FromSource.QQ
import Juvix.Compiler.Nockma.Translation.FromTree
import Juvix.Prelude qualified as Prelude
Expand All @@ -20,12 +19,7 @@ mkAnomaCallTest' enableDebug _testName relRoot mainFile args _testCheck =
where
mkTestIO :: IO Test
mkTestIO = do
anomaRes <- withRootCopy $ \tmpDir -> do
compiledMain :: AnomaResult <- compileMain tmpDir
-- Write out the nockma function to force full evaluation of the compiler
let mainClosure = compiledMain ^. anomaClosure
writeFileEnsureLn (tmpDir <//> $(mkRelFile "test.nockma")) (ppSerialize mainClosure)
return compiledMain
anomaRes <- withRootCopy compileMain
let _testProgramFormula = anomaCall args
_testProgramSubject = anomaRes ^. anomaClosure
_testEvalOptions = defaultEvalOptions
Expand Down
5 changes: 5 additions & 0 deletions tests/Anoma/Compilation/negative/String.juvix
Original file line number Diff line number Diff line change
@@ -0,0 +1,5 @@
module String;

import Stdlib.Prelude open;

main : String := "boom";

0 comments on commit 5afcae5

Please sign in to comment.