1
1
mirror of https://github.com/anoma/juvix.git synced 2024-12-15 01:52:11 +03:00
juvix/test/Internal/Eval/Base.hs
janmasrovira 90a7a5e7e0
Fix REPL state to include enough information to rerun the pipeline (#1911)
Previously we were:
* discarding the types table 
* discarding the name ids state
after processing an expression in the REPL.

For example evaluating:
```
let even : _; odd : _; odd zero := false; odd (suc n) := not (even n); even zero := true; even (suc n) := not (odd n) in even 10
```
would loop in the REPL.

We noticed that the `n` in `suc n` was being given type `Type` instead
of `Nat`. This was because the name id given to n was incorrect, the
REPL started using name ids from 0 again.

We fixed this issue by storing information, including the types table
and name ids state in the Artifacts data structure that is returned when
we run the pipeline for the first time. This information is then used
when we call functions to compile / type check REPL expressions.

---------

Co-authored-by: Paul Cadman <git@paulcadman.dev>
2023-03-30 13:39:27 +02:00

46 lines
1.9 KiB
Haskell

module Internal.Eval.Base where
import Base
import Core.Eval.Base
import Data.HashMap.Strict qualified as HashMap
import Data.Text.IO qualified as TIO
import Juvix.Compiler.Core.Data.InfoTable
import Juvix.Compiler.Core.Extra
import Juvix.Compiler.Core.Info qualified as Info
import Juvix.Compiler.Core.Info.NoDisplayInfo
import Juvix.Compiler.Core.Pretty
import Juvix.Compiler.Core.Transformation (etaExpansionApps)
import Juvix.Compiler.Core.Translation.FromInternal.Data as Core
import Juvix.Compiler.Pipeline
internalCoreAssertion :: Path Abs File -> Path Abs File -> (String -> IO ()) -> Assertion
internalCoreAssertion mainFile expectedFile step = do
step "Translate to Core"
cwd <- getCurrentDir
let entryPoint = defaultEntryPoint cwd mainFile
tab0 <- (^. Core.coreResultTable) . snd <$> runIO' entryPoint upToCore
let tab = etaExpansionApps tab0
case (tab ^. infoMain) >>= ((tab ^. identContext) HashMap.!?) of
Just node -> do
withTempDir'
( \dirPath -> do
let outputFile = dirPath <//> $(mkRelFile "out.out")
hout <- openFile (toFilePath outputFile) WriteMode
step "Evaluate"
r' <- doEval mainFile hout tab node
case r' of
Left err -> do
hClose hout
assertFailure (show (pretty err))
Right value -> do
unless
(Info.member kNoDisplayInfo (getInfo value))
(hPutStrLn hout (ppPrint value))
hClose hout
actualOutput <- TIO.readFile (toFilePath outputFile)
step "Compare expected and actual program output"
expected <- TIO.readFile (toFilePath expectedFile)
assertEqDiffText ("Check: EVAL output = " <> toFilePath expectedFile) actualOutput expected
)
Nothing -> assertFailure ("No main function registered in: " <> toFilePath mainFile)