1
1
mirror of https://github.com/anoma/juvix.git synced 2024-12-14 08:27:03 +03:00
juvix/test/Compilation/Base.hs
Łukasz Czajka 186f4f66ef
Tests for the new compilation pipeline (#1703)
Adds Juvix tests for the compilation pipeline - these are converted from
the JuvixCore tests (those that make sense). Currently, only the
translation from Juvix to JuvixCore is checked for the tests that can be
type-checked. Ultimately, the entire compilation pipeline down to native
code / WebAssembly should be checked on these tests.

Closes #1689
2023-01-12 11:22:32 +01:00

23 lines
807 B
Haskell

module Compilation.Base where
import Base
import Data.HashMap.Strict qualified as HashMap
import Juvix.Compiler.Builtins (iniState)
import Juvix.Compiler.Core.Data.InfoTable qualified as Core
import Juvix.Compiler.Core.Translation.FromInternal.Data qualified as Core
import Juvix.Compiler.Pipeline
compileAssertion ::
Path Abs File ->
Path Abs File ->
(String -> IO ()) ->
Assertion
compileAssertion mainFile _ step = do
step "Translate to JuvixCore"
cwd <- getCurrentDir
let entryPoint = defaultEntryPoint cwd mainFile
tab <- (^. Core.coreResultTable) . snd <$> runIO' iniState entryPoint upToCore
case (tab ^. Core.infoMain) >>= ((tab ^. Core.identContext) HashMap.!?) of
Just _ -> return ()
Nothing -> assertFailure ("No main function registered in: " <> toFilePath mainFile)