1
1
mirror of https://github.com/anoma/juvix.git synced 2024-12-14 17:32:00 +03:00
juvix/app/Commands/Compile.hs
Jan Mas Rovira 69594edc7b
Read Package on demand and cache it (#2548)
This patch dramatically increases the efficiency of `juvix dev root`,
which was unnecessarily parsing all dependencies included in the
`Package.juvix` file. Other commands that do not require the `Package`
will also be faster.

It also refactors some functions so that the `TaggedLock` effect is run
globally.

I've added `singletons-base` as a dependency so we can have `++` on the
type level. We've tried to define a type family ourselves but inference
was not working properly.
2023-12-06 18:24:59 +01:00

39 lines
1.6 KiB
Haskell

module Commands.Compile where
import Commands.Base
import Commands.Compile.Options
import Commands.Dev.Core.Compile.Base qualified as Compile
import Commands.Extra.Compile qualified as Compile
import Data.Text.IO qualified as TIO
import Juvix.Compiler.Core qualified as Core
import Juvix.Compiler.Core.Pretty qualified as Core
import Juvix.Compiler.Core.Transformation.DisambiguateNames qualified as Core
runCommand :: (Members '[Embed IO, App, TaggedLock] r) => CompileOptions -> Sem r ()
runCommand opts@CompileOptions {..} = do
inputFile <- getMainFile _compileInputFile
Core.CoreResult {..} <- runPipeline (AppPath (preFileFromAbs inputFile) True) upToCore
let arg =
Compile.PipelineArg
{ _pipelineArgFile = inputFile,
_pipelineArgOptions = opts,
_pipelineArgInfoTable = _coreResultTable
}
case _compileTarget of
TargetNative64 -> Compile.runCPipeline arg
TargetWasm32Wasi -> Compile.runCPipeline arg
TargetGeb -> Compile.runGebPipeline arg
TargetVampIR -> Compile.runVampIRPipeline arg
TargetCore -> writeCoreFile arg
TargetAsm -> Compile.runAsmPipeline arg
writeCoreFile :: (Members '[Embed IO, App, TaggedLock] r) => Compile.PipelineArg -> Sem r ()
writeCoreFile pa@Compile.PipelineArg {..} = do
entryPoint <- Compile.getEntry pa
coreFile <- Compile.outputFile _pipelineArgOptions _pipelineArgFile
r <- runReader entryPoint $ runError @JuvixError $ Core.toEval _pipelineArgInfoTable
case r of
Left e -> exitJuvixError e
Right tab ->
embed $ TIO.writeFile (toFilePath coreFile) (show $ Core.ppOutDefault (Core.disambiguateNames tab))