1
1
mirror of https://github.com/anoma/juvix.git synced 2024-12-15 01:52:11 +03:00
juvix/test/Asm/Run/Base.hs
Łukasz Czajka f2298bd674
JuvixCore to JuvixAsm translation (#1665)
An implementation of the translation from JuvixCore to JuvixAsm. After
merging this PR, the only remaining step to complete the basic
compilation pipeline (#1556) is the compilation of complex pattern
matching (#1531).

* Fixes several bugs in lambda-lifting.
* Fixes several bugs in the RemoveTypeArgs transformation.
* Fixes several bugs in the TopEtaExpand transformation.
* Adds the ConvertBuiltinTypes transformation which converts the builtin
bool inductive type to Core primitive bool.
* Adds the `juvix dev core strip` command.
* Adds the `juvix dev core asm` command.
* Adds the `juvix dev core compile` command.
* Adds two groups of tests: 
- JuvixCore to JuvixAsm translation: translate JuvixCore tests to
JuvixAsm and run the results with the JuvixAsm interpreter,
- JuvixCore compilation: compile JuvixCore tests to native code and WASM
and execute the results.
* Closes #1520 
* Closes #1549
2023-01-09 18:21:30 +01:00

95 lines
3.4 KiB
Haskell

module Asm.Run.Base where
import Base
import Data.Text.IO qualified as TIO
import Juvix.Compiler.Asm.Data.InfoTable
import Juvix.Compiler.Asm.Error
import Juvix.Compiler.Asm.Extra
import Juvix.Compiler.Asm.Interpreter
import Juvix.Compiler.Asm.Pretty
import Juvix.Compiler.Asm.Transformation.Validate
import Juvix.Compiler.Asm.Translation.FromSource
import Juvix.Data.PPOutput
asmRunAssertion' :: InfoTable -> Path Abs File -> (String -> IO ()) -> Assertion
asmRunAssertion' tab expectedFile step = do
step "Validate"
case validate' tab of
Just err -> assertFailure (show (pretty err))
Nothing ->
case tab ^. infoMainFunction of
Just sym -> do
withTempDir'
( \dirPath -> do
let outputFile = dirPath <//> $(mkRelFile "out.out")
hout <- openFile (toFilePath outputFile) WriteMode
step "Interpret"
r' <- doRun hout tab (getFunInfo tab sym)
case r' of
Left err -> do
hClose hout
assertFailure (show (pretty err))
Right value' -> do
case value' of
ValVoid -> return ()
_ -> hPutStrLn hout (ppPrint tab value')
hClose hout
actualOutput <- TIO.readFile (toFilePath outputFile)
step "Compare expected and actual program output"
expected <- TIO.readFile (toFilePath expectedFile)
assertEqDiff ("Check: RUN output = " <> toFilePath expectedFile) actualOutput expected
)
Nothing -> assertFailure "no 'main' function"
asmRunAssertion :: Path Abs File -> Path Abs File -> (InfoTable -> Either AsmError InfoTable) -> (InfoTable -> Assertion) -> (String -> IO ()) -> Assertion
asmRunAssertion mainFile expectedFile trans testTrans step = do
step "Parse"
r <- parseFile mainFile
case r of
Left err -> assertFailure (show (pretty err))
Right tab0 -> do
case trans tab0 of
Left err -> assertFailure (show (pretty err))
Right tab -> do
testTrans tab
asmRunAssertion' tab expectedFile step
asmRunErrorAssertion :: Path Abs File -> (String -> IO ()) -> Assertion
asmRunErrorAssertion mainFile step = do
step "Parse"
r <- parseFile mainFile
case r of
Left _ -> assertBool "" True
Right tab -> do
step "Validate"
case validate' tab of
Just _ -> assertBool "" True
Nothing ->
case tab ^. infoMainFunction of
Just sym -> do
withTempDir'
( \dirPath -> do
let outputFile = dirPath <//> $(mkRelFile "out.out")
hout <- openFile (toFilePath outputFile) WriteMode
step "Interpret"
r' <- doRun hout tab (getFunInfo tab sym)
hClose hout
case r' of
Left _ -> assertBool "" True
Right _ -> assertFailure "no error"
)
Nothing -> assertBool "" True
parseFile :: Path Abs File -> IO (Either ParserError InfoTable)
parseFile f = do
let f' = toFilePath f
s <- readFile f'
return $ runParser f' s
doRun ::
Handle ->
InfoTable ->
FunctionInfo ->
IO (Either AsmError Val)
doRun hout tab funInfo = catchRunErrorIO (hRunCodeIO stdin hout tab funInfo)