1
1
mirror of https://github.com/anoma/juvix.git synced 2024-12-15 10:03:22 +03:00
juvix/app/Commands/Extra/Compile.hs
Łukasz Czajka 2d798ec31c
New compilation pipeline (#1832)
* Depends on PR #1824 
* Closes #1556 
* Closes #1825 
* Closes #1843
* Closes #1729 
* Closes #1596 
* Closes #1343 
* Closes #1382 
* Closes #1867 
* Closes #1876 
* Changes the `juvix compile` command to use the new pipeline.
* Removes the `juvix dev minic` command and the `BackendC` tests.
* Adds the `juvix eval` command.
* Fixes bugs in the Nat-to-integer conversion.
* Fixes bugs in the Internal-to-Core and Core-to-Core.Stripped
translations.
* Fixes bugs in the RemoveTypeArgs transformation.
* Fixes bugs in lambda-lifting (incorrect de Bruijn indices in the types
of added binders).
* Fixes several other bugs in the compilation pipeline.
* Adds a separate EtaExpandApps transformation to avoid quadratic
runtime in the Internal-to-Core translation due to repeated calls to
etaExpandApps.
* Changes Internal-to-Core to avoid generating matches on values which
don't have an inductive type.

---------

Co-authored-by: Paul Cadman <git@paulcadman.dev>
Co-authored-by: janmasrovira <janmasrovira@gmail.com>
2023-03-14 16:24:07 +01:00

208 lines
7.0 KiB
Haskell

module Commands.Extra.Compile where
import Commands.Base
import Commands.Extra.Compile.Options
import Data.ByteString qualified as BS
import Data.FileEmbed qualified as FE
import Juvix.Extra.Paths
import System.Environment
import System.Process qualified as P
runCommand :: forall r. (Members '[Embed IO, App] r) => CompileOptions -> Sem r ()
runCommand opts = do
inputFile <- someBaseToAbs' (opts ^. compileInputFile . pathPath)
result <- runCompile inputFile opts
case result of
Left err -> printFailureExit err
_ -> return ()
runCompile ::
(Members '[App, Embed IO] r) =>
Path Abs File ->
CompileOptions ->
Sem r (Either Text ())
runCompile inputFile o = do
buildDir <- askBuildDir
ensureDir buildDir
ensureDir (juvixIncludeDir buildDir)
prepareRuntime buildDir o
case o ^. compileTarget of
TargetWasm32Wasi -> runError (clangWasmWasiCompile inputFile o)
TargetNative64 -> runError (clangNativeCompile inputFile o)
TargetGeb -> return $ Right ()
TargetCore -> return $ Right ()
TargetAsm -> return $ Right ()
prepareRuntime :: forall r. (Members '[App, Embed IO] r) => Path Abs Dir -> CompileOptions -> Sem r ()
prepareRuntime buildDir o = do
mapM_ writeHeader headersDir
case o ^. compileTarget of
TargetWasm32Wasi | o ^. compileDebug -> writeRuntime wasiDebugRuntime
TargetWasm32Wasi -> writeRuntime wasiReleaseRuntime
TargetNative64 | o ^. compileDebug -> writeRuntime nativeDebugRuntime
TargetNative64 -> writeRuntime nativeReleaseRuntime
TargetGeb -> return ()
TargetCore -> return ()
TargetAsm -> return ()
where
wasiReleaseRuntime :: BS.ByteString
wasiReleaseRuntime = $(FE.makeRelativeToProject "runtime/_build.wasm32-wasi/libjuvix.a" >>= FE.embedFile)
nativeReleaseRuntime :: BS.ByteString
nativeReleaseRuntime = $(FE.makeRelativeToProject "runtime/_build.native64/libjuvix.a" >>= FE.embedFile)
wasiDebugRuntime :: BS.ByteString
wasiDebugRuntime = $(FE.makeRelativeToProject "runtime/_build.wasm32-wasi-debug/libjuvix.a" >>= FE.embedFile)
nativeDebugRuntime :: BS.ByteString
nativeDebugRuntime = $(FE.makeRelativeToProject "runtime/_build.native64-debug/libjuvix.a" >>= FE.embedFile)
writeRuntime :: BS.ByteString -> Sem r ()
writeRuntime =
embed
. BS.writeFile (toFilePath (buildDir <//> $(mkRelFile "libjuvix.a")))
headersDir :: [(Path Rel File, BS.ByteString)]
headersDir = map (first relFile) $(FE.makeRelativeToProject "runtime/include" >>= FE.embedDir)
includeDir :: Path Abs Dir
includeDir = juvixIncludeDir buildDir
writeHeader :: (Path Rel File, BS.ByteString) -> Sem r ()
writeHeader (filePath, contents) = embed $ do
ensureDir (includeDir <//> parent filePath)
BS.writeFile (toFilePath (includeDir <//> filePath)) contents
outputFile :: Member App r => CompileOptions -> Path Abs File -> Sem r (Path Abs File)
outputFile opts inputFile =
maybe (return defaultOutputFile) someBaseToAbs' (opts ^? compileOutputFile . _Just . pathPath)
where
defaultOutputFile :: Path Abs File
defaultOutputFile = case opts ^. compileTarget of
TargetNative64 ->
if
| opts ^. compileCOutput -> replaceExtension' ".c" inputFile
| opts ^. compilePreprocess -> addExtension' ".c" (addExtension' ".out" (removeExtension' inputFile))
| opts ^. compileAssembly -> replaceExtension' ".s" inputFile
| otherwise -> removeExtension' inputFile
TargetWasm32Wasi ->
if
| opts ^. compileCOutput -> replaceExtension' ".c" inputFile
| opts ^. compilePreprocess -> addExtension' ".c" (addExtension' ".out" (removeExtension' inputFile))
| opts ^. compileAssembly -> replaceExtension' ".wat" inputFile
| otherwise -> replaceExtension' ".wasm" inputFile
TargetGeb ->
if
| opts ^. compileTerm -> replaceExtension' ".geb" inputFile
| otherwise -> replaceExtension' ".lisp" inputFile
TargetCore ->
replaceExtension' ".jvc" inputFile
TargetAsm ->
replaceExtension' ".jva" inputFile
clangNativeCompile ::
forall r.
(Members '[App, Embed IO, Error Text] r) =>
Path Abs File ->
CompileOptions ->
Sem r ()
clangNativeCompile inputFile o = do
outputFile' <- outputFile o inputFile
buildDir <- askBuildDir
if
| o ^. compileCOutput ->
copyFile inputFile outputFile'
| otherwise ->
runClang (native64Args buildDir o outputFile' inputFile)
clangWasmWasiCompile ::
forall r.
(Members '[App, Embed IO, Error Text] r) =>
Path Abs File ->
CompileOptions ->
Sem r ()
clangWasmWasiCompile inputFile o = do
outputFile' <- outputFile o inputFile
buildDir <- askBuildDir
if
| o ^. compileCOutput ->
copyFile inputFile outputFile'
| otherwise -> do
clangArgs <- wasiArgs buildDir o outputFile' inputFile <$> sysrootEnvVar
runClang clangArgs
where
sysrootEnvVar :: Sem r (Path Abs Dir)
sysrootEnvVar =
absDir
<$> fromMaybeM (throw msg) (embed (lookupEnv "WASI_SYSROOT_PATH"))
where
msg :: Text
msg = "Missing environment variable WASI_SYSROOT_PATH"
commonArgs :: Path Abs Dir -> CompileOptions -> Path Abs File -> [String]
commonArgs buildDir o outfile =
["-E" | o ^. compilePreprocess]
<> ["-S" | o ^. compileAssembly]
<> (if o ^. compileDebug then ["-DDEBUG"] else ["-DNDEBUG"])
<> [ "-W",
"-Wall",
"-Wno-unused-parameter",
"-Wno-unused-label",
"-Werror",
"-std=c11",
"-I",
toFilePath (juvixIncludeDir buildDir),
"-o",
toFilePath outfile
]
<> ( if
| not (o ^. compilePreprocess || o ^. compileAssembly) ->
[ "-L",
toFilePath buildDir
]
| otherwise -> []
)
native64Args :: Path Abs Dir -> CompileOptions -> Path Abs File -> Path Abs File -> [String]
native64Args buildDir o outfile inputFile =
commonArgs buildDir o outfile
<> [ "-DARCH_NATIVE64",
"-DAPI_LIBC",
"-m64",
"-O3",
toFilePath inputFile
]
<> ( if
| not (o ^. compilePreprocess || o ^. compileAssembly) ->
["-ljuvix"]
| otherwise -> []
)
wasiArgs :: Path Abs Dir -> CompileOptions -> Path Abs File -> Path Abs File -> Path Abs Dir -> [String]
wasiArgs buildDir o outfile inputFile sysrootPath =
commonArgs buildDir o outfile
<> [ "-DARCH_WASM32",
"-DAPI_WASI",
"-Os",
"-nodefaultlibs",
"--target=wasm32-wasi",
"--sysroot",
toFilePath sysrootPath,
toFilePath inputFile
]
<> ( if
| not (o ^. compilePreprocess || o ^. compileAssembly) ->
["-ljuvix"]
| otherwise -> []
)
runClang ::
(Members '[Embed IO, Error Text] r) =>
[String] ->
Sem r ()
runClang args = do
(exitCode, _, err) <- embed (P.readProcessWithExitCode "clang" args "")
case exitCode of
ExitSuccess -> return ()
_ -> throw (pack err)