-
Notifications
You must be signed in to change notification settings - Fork 57
Commit
This commit does not belong to any branch on this repository, and may belong to a fork outside of the repository.
Add anoma compile negative test for strings
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
1 parent
64a4d09
commit 5afcae5
Showing
5 changed files
with
55 additions
and
11 deletions.
There are no files selected for viewing
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
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] |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
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] |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,5 @@ | ||
module String; | ||
|
||
import Stdlib.Prelude open; | ||
|
||
main : String := "boom"; |