1
1
mirror of https://github.com/anoma/juvix.git synced 2024-11-25 21:35:50 +03:00

Compile-time configuration (#3102)

* Closes #3077 
* Closes #3100 
* Adds a compilation-time configuration script that creates a
`config/config.json` file which is then read by the
`Makefile`/`justfile` and embedded into the Juvix binary.
This commit is contained in:
Łukasz Czajka 2024-10-16 11:47:23 +02:00 committed by GitHub
parent 9fcc49f6e0
commit c50ad06976
No known key found for this signature in database
GPG Key ID: B5690EEEBB952194
28 changed files with 344 additions and 190 deletions

View File

@ -29,6 +29,8 @@ STACK?=stack
JUVIXBIN?=juvix
CC=clang
ifeq ($(UNAME), Darwin)
THREADS := $(shell sysctl -n hw.logicalcpu)
else ifeq ($(UNAME), Linux)
@ -201,8 +203,12 @@ build: submodules runtime
fast-build: submodules runtime
@${STACK} build --fast ${STACKFLAGS}
.PHONY: configure
configure:
CC=${CC} config/configure.sh
.PHONY: runtime
runtime:
runtime: configure
cd runtime && make
# -- Install

View File

@ -11,6 +11,7 @@ import Commands.Compile.Vampir.Options
import Commands.Compile.Wasi.Options
import Commands.Extra.NewCompile
import CommonOptions
import Juvix.Config qualified as Config
data CompileCommand
= Native (NativeOptions 'InputMain)
@ -29,7 +30,7 @@ supportedTargets =
[ (AppTargetVampIR, Vampir <$> parseVampir),
(AppTargetAnoma, Anoma <$> parseAnoma),
(AppTargetCairo, Cairo <$> parseCairo),
(AppTargetWasm32Wasi, Wasi <$> parseWasi),
(AppTargetNative64, Native <$> parseNative),
(AppTargetRiscZeroRust, RiscZeroRust <$> parseRiscZeroRust)
(AppTargetNative64, Native <$> parseNative)
]
<> [(AppTargetWasm32Wasi, Wasi <$> parseWasi) | Config.config ^. Config.configWasm]
<> [(AppTargetRiscZeroRust, RiscZeroRust <$> parseRiscZeroRust) | Config.config ^. Config.configRust]

View File

@ -2,39 +2,11 @@ module Commands.Compile.RiscZeroRust where
import Commands.Base
import Commands.Compile.RiscZeroRust.Options
import Commands.Extra.NewCompile
import Data.FileEmbed qualified as FE
import Commands.Compile.RiscZeroRust.Rust
import Juvix.Compiler.Backend.Rust.Data.Result
runCommand :: forall r. (Members AppEffects r) => RiscZeroRustOptions 'InputMain -> Sem r ()
runCommand opts = do
let opts' = opts ^. riscZeroRustCompileCommonOptions
inputFile = opts' ^. compileInputFile
moutputDir = opts ^. riscZeroRustOutputDir
outDir :: Path Abs Dir <- getOutputDir FileExtRiscZero inputFile moutputDir
writeDirFiles riscZeroDir outDir
let outJuvixSourceDir :: Path Abs Dir = outDir <//> $(mkRelDir "juvix") <//> $(mkRelDir "src")
writeDirFiles rustRuntimeSourceDir outJuvixSourceDir
writeFile (outDir <//> $(mkRelDir "juvix") <//> $(mkRelFile "Cargo.toml")) rustRuntimeToml
let outFile :: Path Abs File =
outDir
<//> $(mkRelDir "methods")
<//> $(mkRelDir "guest")
<//> $(mkRelDir "src")
<//> $(mkRelFile "main.rs")
let inputFile = opts ^. riscZeroRustCompileCommonOptions . compileInputFile
Result {..} <- runPipeline opts inputFile upToRiscZeroRust
writeFileEnsureLn outFile _resultRustCode
where
riscZeroDir :: [(FilePath, ByteString)]
riscZeroDir = $(FE.makeRelativeToProject "runtime/rust/risc0" >>= FE.embedDir)
rustRuntimeSourceDir :: [(FilePath, ByteString)]
rustRuntimeSourceDir = $(FE.makeRelativeToProject "runtime/rust/juvix/src" >>= FE.embedDir)
rustRuntimeToml :: ByteString
rustRuntimeToml = $(FE.makeRelativeToProject "runtime/rust/juvix/Cargo.toml" >>= FE.embedFile)
writeDirFiles :: [(FilePath, ByteString)] -> Path Abs Dir -> Sem r ()
writeDirFiles fs outDir = do
let fs' = map (first relFile) fs
forM_ (first (outDir <//>) <$> fs') (uncurry writeFile)
compileRustCode opts inputFile _resultRustCode

View File

@ -0,0 +1,36 @@
module Commands.Compile.RiscZeroRust.Rust where
import Commands.Base
import Commands.Compile.RiscZeroRust.Options
import Commands.Extra.NewCompile
import Data.FileEmbed qualified as FE
compileRustCode :: forall k r. (Members '[App, TaggedLock, EmbedIO] r) => RiscZeroRustOptions k -> Maybe (AppPath File) -> Text -> Sem r ()
compileRustCode opts inputFile code = do
let moutputDir = opts ^. riscZeroRustOutputDir
outDir :: Path Abs Dir <- getOutputDir FileExtRiscZero inputFile moutputDir
writeDirFiles riscZeroDir outDir
let outJuvixSourceDir :: Path Abs Dir = outDir <//> $(mkRelDir "juvix") <//> $(mkRelDir "src")
writeDirFiles rustRuntimeSourceDir outJuvixSourceDir
writeFile (outDir <//> $(mkRelDir "juvix") <//> $(mkRelFile "Cargo.toml")) rustRuntimeToml
let outFile :: Path Abs File =
outDir
<//> $(mkRelDir "methods")
<//> $(mkRelDir "guest")
<//> $(mkRelDir "src")
<//> $(mkRelFile "main.rs")
writeFileEnsureLn outFile code
where
riscZeroDir :: [(FilePath, ByteString)]
riscZeroDir = $(FE.makeRelativeToProject "runtime/rust/risc0" >>= FE.embedDir)
rustRuntimeSourceDir :: [(FilePath, ByteString)]
rustRuntimeSourceDir = $(FE.makeRelativeToProject "runtime/rust/juvix/src" >>= FE.embedDir)
rustRuntimeToml :: ByteString
rustRuntimeToml = $(FE.makeRelativeToProject "runtime/rust/juvix/Cargo.toml" >>= FE.embedFile)
writeDirFiles :: [(FilePath, ByteString)] -> Path Abs Dir -> Sem r ()
writeDirFiles fs outDir = do
let fs' = map (first relFile) fs
forM_ (first (outDir <//>) <$> fs') (uncurry writeFile)

View File

@ -44,18 +44,18 @@ wasiHelperOptions opts =
forall s.
(Members '[App, EmbedIO] s) =>
Sem s ()
prepareRuntime = writeRuntime runtime
prepareRuntime = writeRuntime (fromJust runtime)
where
runtime :: BS.ByteString
runtime :: Maybe BS.ByteString
runtime
| opts ^. wasiCompileCommonOptions . compileDebug = wasiDebugRuntime
| otherwise = wasiReleaseRuntime
where
wasiReleaseRuntime :: BS.ByteString
wasiReleaseRuntime = $(FE.makeRelativeToProject "runtime/c/_build.wasm32-wasi/libjuvix.a" >>= FE.embedFile)
wasiReleaseRuntime :: Maybe BS.ByteString
wasiReleaseRuntime = $(FE.makeRelativeToProject "runtime/c/_build.wasm32-wasi/libjuvix.a" >>= FE.embedFileIfExists)
wasiDebugRuntime :: BS.ByteString
wasiDebugRuntime = $(FE.makeRelativeToProject "runtime/c/_build.wasm32-wasi-debug/libjuvix.a" >>= FE.embedFile)
wasiDebugRuntime :: Maybe BS.ByteString
wasiDebugRuntime = $(FE.makeRelativeToProject "runtime/c/_build.wasm32-wasi-debug/libjuvix.a" >>= FE.embedFileIfExists)
wasiDefaultOutputFile :: Path Abs File -> Path Abs File -> Path Abs File
wasiDefaultOutputFile inputFile baseOutputFile =

View File

@ -6,17 +6,19 @@ where
import Commands.Extra.Compile.Options
import CommonOptions
import Juvix.Config qualified as Config
type AsmCompileOptions = CompileOptions
asmSupportedTargets :: NonEmpty CompileTarget
asmSupportedTargets =
AppTargetWasm32Wasi
:| [ AppTargetNative64,
AppTargetReg,
AppTargetNative64
:| [ AppTargetReg,
AppTargetCasm,
AppTargetCairo
]
<> [AppTargetWasm32Wasi | Config.config ^. Config.configWasm]
<> [AppTargetRiscZeroRust | Config.config ^. Config.configRust]
parseAsmCompileOptions :: Parser AsmCompileOptions
parseAsmCompileOptions =

View File

@ -7,22 +7,23 @@ where
import Commands.Extra.Compile.Options
import CommonOptions
import Data.List.NonEmpty qualified as NonEmpty
import Juvix.Config qualified as Config
type CoreCompileOptions = CompileOptions
coreSupportedTargets :: NonEmpty CompileTarget
coreSupportedTargets =
NonEmpty.fromList
NonEmpty.fromList $
[ AppTargetNative64,
AppTargetWasm32Wasi,
AppTargetVampIR,
AppTargetTree,
AppTargetAsm,
AppTargetReg,
AppTargetCasm,
AppTargetCairo,
AppTargetRiscZeroRust
AppTargetCairo
]
<> [AppTargetWasm32Wasi | Config.config ^. Config.configWasm]
<> [AppTargetRiscZeroRust | Config.config ^. Config.configRust]
parseCoreCompileOptions :: Parser CoreCompileOptions
parseCoreCompileOptions =

View File

@ -36,18 +36,18 @@ runCommand opts = do
forall s.
(Members '[App, EmbedIO] s) =>
Sem s ()
prepareRuntime = writeRuntime runtime
prepareRuntime = writeRuntime (fromJust runtime)
where
runtime :: BS.ByteString
runtime :: Maybe BS.ByteString
runtime
| opts ^. nativeRustCompileCommonOptions . compileDebug = rustDebugRuntime
| otherwise = rustReleaseRuntime
where
rustReleaseRuntime :: BS.ByteString
rustReleaseRuntime = $(FE.makeRelativeToProject "runtime/rust/juvix/target/release/libjuvix.rlib" >>= FE.embedFile)
rustReleaseRuntime :: Maybe BS.ByteString
rustReleaseRuntime = $(FE.makeRelativeToProject "runtime/rust/juvix/target/release/libjuvix.rlib" >>= FE.embedFileIfExists)
rustDebugRuntime :: BS.ByteString
rustDebugRuntime = $(FE.makeRelativeToProject "runtime/rust/juvix/target/debug/libjuvix.rlib" >>= FE.embedFile)
rustDebugRuntime :: Maybe BS.ByteString
rustDebugRuntime = $(FE.makeRelativeToProject "runtime/rust/juvix/target/debug/libjuvix.rlib" >>= FE.embedFileIfExists)
inputRustFile :: (Members '[App, EmbedIO] r) => Path Abs File -> Sem r (Path Abs File)
inputRustFile inputFileCompile = do

View File

@ -8,6 +8,7 @@ import Commands.Dev.DevCompile.Reg.Options
import Commands.Dev.DevCompile.Rust.Options
import Commands.Dev.DevCompile.Tree.Options
import CommonOptions
import Juvix.Config qualified as Config
data DevCompileCommand
= Core (CoreOptions 'InputMain)
@ -22,15 +23,15 @@ data DevCompileCommand
parseDevCompileCommand :: Parser DevCompileCommand
parseDevCompileCommand =
hsubparser
( mconcat
( mconcat $
[ commandCore,
commandReg,
commandTree,
commandCasm,
commandAsm,
commandRust,
commandNativeRust
commandAsm
]
<> [commandRust | Config.config ^. Config.configRust]
<> [commandNativeRust | Config.config ^. Config.configRust]
)
commandCore :: Mod CommandFields DevCompileCommand

View File

@ -6,14 +6,16 @@ where
import Commands.Extra.Compile.Options
import CommonOptions
import Juvix.Config qualified as Config
regSupportedTargets :: NonEmpty CompileTarget
regSupportedTargets =
AppTargetNative64
:| [ AppTargetWasm32Wasi,
AppTargetCasm,
:| [ AppTargetCasm,
AppTargetCairo
]
<> [AppTargetWasm32Wasi | Config.config ^. Config.configWasm]
<> [AppTargetRiscZeroRust | Config.config ^. Config.configRust]
parseRegCompileOptions :: Parser CompileOptions
parseRegCompileOptions =

View File

@ -2,6 +2,7 @@ module Commands.Dev.Runtime.Options where
import Commands.Dev.Runtime.Compile.Options
import CommonOptions
import Juvix.Config qualified as Config
newtype RuntimeCommand
= Compile CompileOptions
@ -10,8 +11,7 @@ newtype RuntimeCommand
runtimeSupportedTargets :: NonEmpty CompileTarget
runtimeSupportedTargets =
AppTargetNative64
:| [ AppTargetWasm32Wasi
]
:| [AppTargetWasm32Wasi | Config.config ^. Config.configWasm]
parseRuntimeOptions :: Parser CompileOptions
parseRuntimeOptions =

View File

@ -8,6 +8,7 @@ import Commands.Dev.Tree.Compile.Casm qualified as Casm
import Commands.Dev.Tree.Compile.Native qualified as Native
import Commands.Dev.Tree.Compile.Options
import Commands.Dev.Tree.Compile.Reg qualified as Reg
import Commands.Dev.Tree.Compile.RiscZeroRust qualified as RiscZeroRust
import Commands.Dev.Tree.Compile.Wasi qualified as Wasi
runCommand ::
@ -23,3 +24,4 @@ runCommand = \case
Reg opts -> Reg.runCommand opts
Anoma opts -> Anoma.runCommand opts
Cairo opts -> Cairo.runCommand opts
RiscZeroRust opts -> RiscZeroRust.runCommand opts

View File

@ -6,6 +6,7 @@ where
import Commands.Compile.Anoma.Options
import Commands.Compile.Cairo.Options
import Commands.Compile.Native.Options
import Commands.Compile.RiscZeroRust.Options
import Commands.Compile.Wasi.Options
import Commands.Dev.DevCompile.Asm.Options
import Commands.Dev.DevCompile.Casm.Options
@ -13,6 +14,7 @@ import Commands.Dev.DevCompile.Reg.Options
import Commands.Extra.Compile.Options
import Commands.Extra.NewCompile
import CommonOptions
import Juvix.Config qualified as Config
data CompileCommand
= Native (NativeOptions ('InputExtension 'FileExtJuvixTree))
@ -22,29 +24,20 @@ data CompileCommand
| Casm (CasmOptions ('InputExtension 'FileExtJuvixTree))
| Anoma (AnomaOptions ('InputExtension 'FileExtJuvixTree))
| Cairo (CairoOptions ('InputExtension 'FileExtJuvixTree))
| RiscZeroRust (RiscZeroRustOptions ('InputExtension 'FileExtJuvixTree))
deriving stock (Data)
treeSupportedTargets :: SupportedTargets
treeSupportedTargets =
AppTargetNative64
:| [ AppTargetWasm32Wasi,
AppTargetAsm,
AppTargetReg,
AppTargetCasm,
AppTargetCairo,
AppTargetAnoma
]
supportedTargets :: [(CompileTarget, Parser CompileCommand)]
supportedTargets =
[ (AppTargetNative64, Native <$> parseNative),
(AppTargetWasm32Wasi, Wasi <$> parseWasi),
(AppTargetAsm, Asm <$> parseAsm),
(AppTargetReg, Reg <$> parseReg),
(AppTargetCasm, Casm <$> parseCasm),
(AppTargetAnoma, Anoma <$> parseAnoma),
(AppTargetCairo, Cairo <$> parseCairo)
]
<> [(AppTargetWasm32Wasi, Wasi <$> parseWasi) | Config.config ^. Config.configWasm]
<> [(AppTargetRiscZeroRust, RiscZeroRust <$> parseRiscZeroRust) | Config.config ^. Config.configRust]
parseCompileCommand :: Parser CompileCommand
parseCompileCommand = commandTargetsHelper supportedTargets

View File

@ -0,0 +1,27 @@
module Commands.Dev.Tree.Compile.RiscZeroRust where
import Commands.Base
import Commands.Compile.RiscZeroRust.Options
import Commands.Compile.RiscZeroRust.Rust
import Juvix.Compiler.Backend.Rust.Data.Result
import Juvix.Compiler.Tree.Data.InfoTable
import Juvix.Compiler.Tree.Translation.FromSource qualified as Tree
runCommand ::
(Members '[App, TaggedLock, EmbedIO] r) =>
RiscZeroRustOptions ('InputExtension 'FileExtJuvixTree) ->
Sem r ()
runCommand opts = do
let inputFile = Just $ opts ^. riscZeroRustCompileCommonOptions . compileInputFile
mainFile <- getMainFile inputFile
tab :: InfoTable <- readFile mainFile >>= getRight . Tree.runParser mainFile
entrypoint <-
applyOptions opts
<$> getEntryPoint inputFile
Result {..} <-
getRight
. run
. runError @JuvixError
. runReader entrypoint
$ treeToRiscZeroRust tab
compileRustCode opts inputFile _resultRustCode

View File

@ -6,17 +6,19 @@ where
import Commands.Extra.Compile.Options
import CommonOptions
import Juvix.Config qualified as Config
treeSupportedTargets :: SupportedTargets
treeSupportedTargets =
AppTargetNative64
:| [ AppTargetWasm32Wasi,
AppTargetAsm,
:| [ AppTargetAsm,
AppTargetReg,
AppTargetCasm,
AppTargetCairo,
AppTargetAnoma
]
<> [AppTargetWasm32Wasi | Config.config ^. Config.configWasm]
<> [AppTargetRiscZeroRust | Config.config ^. Config.configRust]
parseTreeCompileOptions :: Parser CompileOptions
parseTreeCompileOptions =

View File

@ -2,9 +2,9 @@ module Commands.Doctor where
import Commands.Base hiding (info)
import Commands.Doctor.Options
import Commands.Extra.Compile
import Data.Aeson
import Data.Aeson.TH
import Juvix.Extra.Clang
import Juvix.Extra.Version qualified as V
import Network.HTTP.Simple
import Safe (headMay)

View File

@ -7,9 +7,9 @@ where
import Commands.Base
import Commands.Compile.CStage
import Commands.Extra.Clang.Backend
import Juvix.Extra.Clang
import Juvix.Extra.Paths
import Juvix.Prelude.Env
import System.Environment
import System.Process qualified as P
data ClangArgs = ClangArgs
@ -135,42 +135,3 @@ runClang args = do
clangNotFoundErr :: Text
clangNotFoundErr = "Error: The clang executable was not found. Please install the LLVM toolchain"
data ClangPath
= ClangSystemPath (Path Abs File)
| ClangEnvVarPath (Path Abs File)
-- | Try searching clang JUVIX_LLVM_DIST_PATH. Otherwise use the PATH
findClang :: (Member EmbedIO r) => Sem r (Maybe ClangPath)
findClang = do
envVarPath <- findClangUsingEnvVar
case envVarPath of
Just p -> return (Just (ClangEnvVarPath p))
Nothing -> (fmap . fmap) ClangSystemPath findClangOnPath
findClangUsingEnvVar :: forall r. (Member EmbedIO r) => Sem r (Maybe (Path Abs File))
findClangUsingEnvVar = do
p <- clangBinPath
join <$> mapM checkExecutable p
where
checkExecutable :: Path Abs File -> Sem r (Maybe (Path Abs File))
checkExecutable p = whenMaybeM (liftIO (isExecutable p)) (return p)
clangBinPath :: Sem r (Maybe (Path Abs File))
clangBinPath = fmap (<//> $(mkRelFile "bin/clang")) <$> llvmDistPath
llvmDistPath :: Sem r (Maybe (Path Abs Dir))
llvmDistPath = liftIO $ do
p <- lookupEnv llvmDistEnvironmentVar
mapM parseAbsDir p
extractClangPath :: ClangPath -> Path Abs File
extractClangPath = \case
ClangSystemPath p -> p
ClangEnvVarPath p -> p
llvmDistEnvironmentVar :: String
llvmDistEnvironmentVar = "JUVIX_LLVM_DIST_PATH"
findClangOnPath :: (Member EmbedIO r) => Sem r (Maybe (Path Abs File))
findClangOnPath = findExecutable $(mkRelFile "clang")

View File

@ -5,6 +5,7 @@ import Commands.Base
import Commands.Extra.Compile.Options
import Data.ByteString qualified as BS
import Data.FileEmbed qualified as FE
import Juvix.Extra.Clang
import Juvix.Extra.Paths
import System.Environment
import System.Process qualified as P
@ -42,8 +43,8 @@ prepareRuntime buildDir o = do
mapM_ writeHeader headersDir
case o ^. compileTarget of
AppTargetWasm32Wasi
| o ^. compileDebug -> writeRuntime wasiDebugRuntime
AppTargetWasm32Wasi -> writeRuntime wasiReleaseRuntime
| o ^. compileDebug -> writeRuntime (fromJust wasiDebugRuntime)
AppTargetWasm32Wasi -> writeRuntime (fromJust wasiReleaseRuntime)
AppTargetNative64
| o ^. compileDebug -> writeRuntime nativeDebugRuntime
AppTargetNative64 -> writeRuntime nativeReleaseRuntime
@ -57,14 +58,14 @@ prepareRuntime buildDir o = do
AppTargetCairo -> return ()
AppTargetRiscZeroRust -> return ()
where
wasiReleaseRuntime :: BS.ByteString
wasiReleaseRuntime = $(FE.makeRelativeToProject "runtime/c/_build.wasm32-wasi/libjuvix.a" >>= FE.embedFile)
wasiReleaseRuntime :: Maybe BS.ByteString
wasiReleaseRuntime = $(FE.makeRelativeToProject "runtime/c/_build.wasm32-wasi/libjuvix.a" >>= FE.embedFileIfExists)
nativeReleaseRuntime :: BS.ByteString
nativeReleaseRuntime = $(FE.makeRelativeToProject "runtime/c/_build.native64/libjuvix.a" >>= FE.embedFile)
wasiDebugRuntime :: BS.ByteString
wasiDebugRuntime = $(FE.makeRelativeToProject "runtime/c/_build.wasm32-wasi-debug/libjuvix.a" >>= FE.embedFile)
wasiDebugRuntime :: Maybe BS.ByteString
wasiDebugRuntime = $(FE.makeRelativeToProject "runtime/c/_build.wasm32-wasi-debug/libjuvix.a" >>= FE.embedFileIfExists)
nativeDebugRuntime :: BS.ByteString
nativeDebugRuntime = $(FE.makeRelativeToProject "runtime/c/_build.native64-debug/libjuvix.a" >>= FE.embedFile)
@ -229,42 +230,6 @@ wasiArgs buildDir o outfile inputFile sysrootPath =
| otherwise -> []
)
findClangOnPath :: (Member EmbedIO r) => Sem r (Maybe (Path Abs File))
findClangOnPath = findExecutable $(mkRelFile "clang")
findClangUsingEnvVar :: forall r. (Member EmbedIO r) => Sem r (Maybe (Path Abs File))
findClangUsingEnvVar = do
p <- clangBinPath
join <$> mapM checkExecutable p
where
checkExecutable :: Path Abs File -> Sem r (Maybe (Path Abs File))
checkExecutable p = whenMaybeM (liftIO (isExecutable p)) (return p)
clangBinPath :: Sem r (Maybe (Path Abs File))
clangBinPath = fmap (<//> $(mkRelFile "bin/clang")) <$> llvmDistPath
llvmDistPath :: Sem r (Maybe (Path Abs Dir))
llvmDistPath = liftIO $ do
p <- lookupEnv llvmDistEnvironmentVar
mapM parseAbsDir p
data ClangPath
= ClangSystemPath (Path Abs File)
| ClangEnvVarPath (Path Abs File)
extractClangPath :: ClangPath -> Path Abs File
extractClangPath = \case
ClangSystemPath p -> p
ClangEnvVarPath p -> p
--- Try searching clang JUVIX_LLVM_DIST_PATH. Otherwise use the PATH
findClang :: (Member EmbedIO r) => Sem r (Maybe ClangPath)
findClang = do
envVarPath <- findClangUsingEnvVar
case envVarPath of
Just p -> return (Just (ClangEnvVarPath p))
Nothing -> (fmap . fmap) ClangSystemPath findClangOnPath
runClang ::
forall r.
(Members '[App, EmbedIO] r) =>
@ -290,6 +255,3 @@ debugClangOptimizationLevel = 1
defaultClangOptimizationLevel :: Int
defaultClangOptimizationLevel = 1
llvmDistEnvironmentVar :: String
llvmDistEnvironmentVar = "JUVIX_LLVM_DIST_PATH"

6
config/config.json Normal file
View File

@ -0,0 +1,6 @@
{
"wasm": true,
"rust": true,
"clang": "clang",
"cargo": "cargo"
}

35
config/configure.sh Executable file
View File

@ -0,0 +1,35 @@
#!/usr/bin/env bash
if [ ! -d "config" ]; then
printf "This script should be run from the root of the project.\n" 1>&2
exit 1
fi
if [ -z "$CC" ]; then
CC="clang"
fi
if [ -z "$CARGO" ]; then
CARGO="cargo"
fi
if $CC -target wasm32-wasi --print-supported-cpus >/dev/null 2>&1; then
WASM="true"
else
WASM="false"
fi
if $CARGO --version >/dev/null 2>&1; then
RUST="true"
else
RUST="false"
fi
cat <<EOF > config/config.json
{
"wasm": $WASM,
"rust": $RUST,
"clang": "$CC",
"cargo": "$CARGO"
}
EOF

View File

@ -105,8 +105,12 @@ test *filter:
run-profile +cmd:
cabal run --enable-profiling juvix -- {{ cmd }} +RTS -p
# Compile-time configuration
configure:
{{ runtimeCcFlag }} config/configure.sh
# Build the juvix runtime
_buildRuntime:
_buildRuntime: configure
cd runtime && make {{ runtimeArgs }}
# Build the project. `build runtime` builds only the runtime.
@ -118,10 +122,10 @@ build *opts:
case $opts in
runtime)
just runtimeArgs="{{ runtimeArgs }}" _buildRuntime
just runtimeCcArg="{{ runtimeCcArg }}" runtimeArgs="{{ runtimeArgs }}" _buildRuntime
;;
*)
just runtimeArgs="{{ runtimeArgs }}" _buildRuntime
just runtimeCcArg="{{ runtimeCcArg }}" runtimeArgs="{{ runtimeArgs }}" _buildRuntime
set -x
{{ stack }} build {{ stackArgs }}
;;

View File

@ -43,6 +43,8 @@ extra-source-files:
- runtime/vampir/*.pir
- runtime/casm/*.casm
- runtime/nockma/*.nockma
- config/config.json
- config/configure.sh
dependencies:
- aeson-better-errors == 0.9.*

View File

@ -7,12 +7,20 @@ all: juvix_c juvix_rust
# 2024-09-20: `-j` cannot be used in the juvix_c make invocation because it causes
# an error in the 'Build Linux static binary workflow'.
.PHONY: juvix_c
juvix_c:
cd c && $(MAKE) -s
juvix_c: juvix_c_native juvix_c_wasm
cd c && $(MAKE) -s includes
.PHONY: juvix_c_native
juvix_c_native:
cd c && $(MAKE) -s native64 native64-debug
.PHONY: juvix_c_wasm
juvix_c_wasm:
if grep -q '"wasm": true' ../config/config.json; then cd c && $(MAKE) -s wasm32-wasi wasm32-wasi-debug; fi
.PHONY: juvix_rust
juvix_rust:
cd rust/juvix && cargo build && cargo build --release
if grep -q '"rust": true' ../config/config.json; then cd rust/juvix && cargo build && cargo build --release; fi
.PHONY: clean
clean:

View File

@ -322,6 +322,15 @@ treeToCasm = treeToCairoAsm >=> asmToCasm
treeToCairo :: (Members '[Error JuvixError, Reader EntryPoint] r) => Tree.InfoTable -> Sem r Cairo.Result
treeToCairo = treeToCasm >=> casmToCairo
treeToRust' :: (Members '[Error JuvixError, Reader EntryPoint] r) => Rust.Backend -> Tree.InfoTable -> Sem r Rust.Result
treeToRust' backend = treeToReg >=> regToRust' backend
treeToRust :: (Members '[Error JuvixError, Reader EntryPoint] r) => Tree.InfoTable -> Sem r Rust.Result
treeToRust = treeToRust' Rust.BackendRust
treeToRiscZeroRust :: (Members '[Error JuvixError, Reader EntryPoint] r) => Tree.InfoTable -> Sem r Rust.Result
treeToRiscZeroRust = treeToRust' Rust.BackendRiscZero
asmToReg :: (Members '[Error JuvixError, Reader EntryPoint] r) => Asm.InfoTable -> Sem r Reg.InfoTable
asmToReg = Asm.toReg >=> return . Reg.fromAsm

39
src/Juvix/Config.hs Normal file
View File

@ -0,0 +1,39 @@
module Juvix.Config where
import Data.Aeson
import Data.ByteString.Lazy qualified as BL
import Data.FileEmbed qualified as FE
import Juvix.Prelude
data Config = Config
{ _configWasm :: Bool,
_configRust :: Bool,
_configClang :: Text,
_configCargo :: Text
}
deriving stock (Show, Eq, Generic)
makeLenses ''Config
instance FromJSON Config where
parseJSON = genericParseJSON opts
where
opts =
defaultOptions
{ fieldLabelModifier = map toLower . dropPrefix "_config"
}
emptyConfig :: Config
emptyConfig =
Config
{ _configWasm = False,
_configRust = False,
_configClang = "",
_configCargo = ""
}
config :: Config
config =
fromMaybe emptyConfig $
decode $
BL.fromStrict $(FE.makeRelativeToProject "config/config.json" >>= FE.embedFile)

75
src/Juvix/Extra/Clang.hs Normal file
View File

@ -0,0 +1,75 @@
module Juvix.Extra.Clang where
import Juvix.Config qualified as Config
import Juvix.Prelude
import System.Environment
import System.FilePath
data ClangPath
= ClangSystemPath (Path Abs File)
| ClangEnvVarPath (Path Abs File)
-- | If the path specified in Config is absolute, try using it. Otherwise, try
-- searching the relative path to clang in JUVIX_LLVM_DIST_PATH. Otherwise use
-- the PATH.
findClang :: (Member EmbedIO r) => Sem r (Maybe ClangPath)
findClang = do
mp <- findClangFromConfig
case mp of
Just p -> return (Just (ClangSystemPath p))
Nothing -> do
envVarPath <- findClangUsingEnvVar
case envVarPath of
Just p -> return (Just (ClangEnvVarPath p))
Nothing -> (fmap . fmap) ClangSystemPath findClangOnPath
checkExecutable :: forall r. (Member EmbedIO r) => Path Abs File -> Sem r (Maybe (Path Abs File))
checkExecutable p = whenMaybeM (liftIO (isExecutable p)) (return p)
findClangFromConfig :: forall r. (Member EmbedIO r) => Sem r (Maybe (Path Abs File))
findClangFromConfig =
if
| isAbsolute clangPath -> do
let p :: Maybe (Path Abs File)
p = parseAbsFile clangPath
join <$> mapM checkExecutable p
| otherwise -> return Nothing
where
clangPath :: FilePath
clangPath = unpack $ Config.config ^. Config.configClang
findClangRelPath :: Maybe (Path Rel File)
findClangRelPath = parseRelFile (unpack $ Config.config ^. Config.configClang)
findClangUsingEnvVar' :: forall r. (Member EmbedIO r) => Path Rel File -> Sem r (Maybe (Path Abs File))
findClangUsingEnvVar' clangRelPath = do
p <- clangBinPath
join <$> mapM checkExecutable p
where
clangBinPath :: Sem r (Maybe (Path Abs File))
clangBinPath = fmap (<//> $(mkRelDir "bin") <//> clangRelPath) <$> llvmDistPath
llvmDistPath :: Sem r (Maybe (Path Abs Dir))
llvmDistPath = liftIO $ do
p <- lookupEnv llvmDistEnvironmentVar
mapM parseAbsDir p
findClangUsingEnvVar :: forall r. (Member EmbedIO r) => Sem r (Maybe (Path Abs File))
findClangUsingEnvVar =
case findClangRelPath of
Just clangRelPath -> findClangUsingEnvVar' clangRelPath
Nothing -> findClangUsingEnvVar' $(mkRelFile "clang")
extractClangPath :: ClangPath -> Path Abs File
extractClangPath = \case
ClangSystemPath p -> p
ClangEnvVarPath p -> p
llvmDistEnvironmentVar :: String
llvmDistEnvironmentVar = "JUVIX_LLVM_DIST_PATH"
findClangOnPath :: (Member EmbedIO r) => Sem r (Maybe (Path Abs File))
findClangOnPath =
case findClangRelPath of
Just clangRelPath -> findExecutable clangRelPath
Nothing -> findExecutable $(mkRelFile "clang")

View File

@ -12,6 +12,7 @@ import Format qualified
import Formatter qualified
import Internal qualified
import Isabelle qualified
import Juvix.Config qualified as Config
import Nockma qualified
import Package qualified
import Parsing qualified
@ -40,12 +41,12 @@ slowTests =
return Internal.allTests,
return Compilation.allTests,
return Examples.allTests,
Rust.allTests,
Casm.allTests,
VampIR.allTests,
return Anoma.allTests,
return Repl.allTests
]
<> sequence (if Config.config ^. Config.configRust then [Rust.allTests] else [])
fastTests :: IO TestTree
fastTests =

View File

@ -2,6 +2,8 @@ module Runtime.Base where
import Base
import Data.FileEmbed
import Juvix.Config qualified as Config
import Juvix.Extra.Clang
import System.Process qualified as P
clangCompile ::
@ -11,26 +13,27 @@ clangCompile ::
(Path Abs File -> IO Text) ->
(String -> IO ()) ->
IO Text
clangCompile mkClangArgs inputFile outputFile execute step =
withTempDir'
( \dirPath -> do
let outputFile' = dirPath <//> outputFile
step "C compilation"
P.callProcess
"clang"
(mkClangArgs outputFile' inputFile)
step "Execution"
execute outputFile'
)
clangCompile mkClangArgs inputFile outputFile execute step = do
mp <- fmap extractClangPath <$> runM findClang
case mp of
Just clangPath ->
withTempDir'
( \dirPath -> do
let outputFile' = dirPath <//> outputFile
step "C compilation"
P.callProcess
(toFilePath clangPath)
(mkClangArgs outputFile' inputFile)
step "Execution"
execute outputFile'
)
Nothing -> assertFailure "clang not found"
clangAssertion :: Int -> Path Abs File -> Path Abs File -> Text -> ((String -> IO ()) -> Assertion)
clangAssertion optLevel inputFile expectedFile stdinText step = do
step "Check clang and wasmer are on path"
assertCmdExists $(mkRelFile "clang")
assertCmdExists $(mkRelFile "wasmer")
step "Lookup WASI_SYSROOT_PATH"
sysrootPath :: Path Abs Dir <- getWasiSysrootPath
when (Config.config ^. Config.configWasm) $ do
step "Check wasmer is on path"
assertCmdExists $(mkRelFile "wasmer")
expected <- readFile expectedFile
@ -40,10 +43,14 @@ clangAssertion optLevel inputFile expectedFile stdinText step = do
let executeNative :: Path Abs File -> IO Text
executeNative outputFile = readProcess (toFilePath outputFile) [] stdinText
step "Compile C to WASM32-WASI"
actualWasm <- clangCompile (wasiArgs optLevel sysrootPath) inputFile $(mkRelFile "Program.wasm") executeWasm step
step "Compare expected and actual program output"
assertEqDiffText ("check: WASM output = " <> toFilePath expectedFile) actualWasm expected
when (Config.config ^. Config.configWasm) $ do
step "Lookup WASI_SYSROOT_PATH"
sysrootPath :: Path Abs Dir <- getWasiSysrootPath
step "Compile C to WASM32-WASI"
actualWasm <- clangCompile (wasiArgs optLevel sysrootPath) inputFile $(mkRelFile "Program.wasm") executeWasm step
step "Compare expected and actual program output"
assertEqDiffText ("check: WASM output = " <> toFilePath expectedFile) actualWasm expected
step "Compile C to native 64-bit code"
actualNative <- clangCompile (native64Args optLevel) inputFile $(mkRelFile "Program") executeNative step