mirror of
https://github.com/anoma/juvix.git
synced 2024-12-12 14:28:08 +03:00
73364f4887
This PR is a snapshot of the current work on the JuvixAsm -> Nockma
translation. The compilation of Juvix programs to Nockma now works so we
decided to raise this PR now to avoid it getting too large.
## Juvix -> Nockma compilation
You can compile a frontend Juvix file to Nockma as follows:
example.juvix
```
module example;
import Stdlib.Prelude open;
fib : Nat → Nat → Nat → Nat
| zero x1 _ := x1
| (suc n) x1 x2 := fib n x2 (x1 + x2);
fibonacci (n : Nat) : Nat := fib n 0 1;
sumList (xs : List Nat) : Nat :=
for (acc := 0) (x in xs)
acc + x;
main : Nat := fibonacci 9 + sumList [1; 2; 3; 4];
```
```
$ juvix compile -t nockma example.juvix
```
This will generate a file `example.nockma` which can be run using the
nockma evaluator:
```
$ juvix dev nockma eval example.nockma
```
Alternatively you can compile JuvixAsm to Nockma:
```
$ juvix dev asm compile -t nockma example.jva
```
## Tests
We compile an evaluate the JuvixAsm tests in
cb3659e08e/test/Nockma/Compile/Asm/Positive.hs
We currently skip some because either:
1. They are too slow to run in the current evaluator (due to arithmetic
operations using the unjetted nock code from the anoma nock stdlib).
2. They trace data types like lists and booleans which are represented
differently by the asm interpreter and the nock interpreter
3. They operate on raw negative numbers, nock only supports raw natural
numbers
## Next steps
On top of this PR we will work on improving the evaluator so that we can
enable the slow compilation tests.
---------
Co-authored-by: Paul Cadman <git@paulcadman.dev>
Co-authored-by: Lukasz Czajka <lukasz@heliax.dev>
239 lines
8.7 KiB
Haskell
239 lines
8.7 KiB
Haskell
module App where
|
|
|
|
import CommonOptions
|
|
import Data.ByteString qualified as ByteString
|
|
import GlobalOptions
|
|
import Juvix.Compiler.Internal.Translation (InternalTypedResult)
|
|
import Juvix.Compiler.Internal.Translation.FromInternal.Analysis.Termination.Checker
|
|
import Juvix.Compiler.Pipeline.Loader.PathResolver
|
|
import Juvix.Compiler.Pipeline.Root
|
|
import Juvix.Compiler.Pipeline.Run
|
|
import Juvix.Data.Error qualified as Error
|
|
import Juvix.Extra.Paths.Base hiding (rootBuildDir)
|
|
import Juvix.Prelude.Pretty hiding
|
|
( Doc,
|
|
)
|
|
import System.Console.ANSI qualified as Ansi
|
|
|
|
data App m a where
|
|
ExitMsg :: ExitCode -> Text -> App m a
|
|
ExitFailMsg :: Text -> App m a
|
|
ExitJuvixError :: JuvixError -> App m a
|
|
PrintJuvixError :: JuvixError -> App m ()
|
|
AskRoot :: App m Root
|
|
AskArgs :: App m RunAppIOArgs
|
|
AskInvokeDir :: App m (Path Abs Dir)
|
|
AskPkgDir :: App m (Path Abs Dir)
|
|
AskBuildDir :: App m (Path Abs Dir)
|
|
AskPackage :: App m Package
|
|
AskPackageGlobal :: App m Bool
|
|
AskGlobalOptions :: App m GlobalOptions
|
|
FromAppPathFile :: AppPath File -> App m (Path Abs File)
|
|
GetMainFile :: Maybe (AppPath File) -> App m (Path Abs File)
|
|
FromAppPathDir :: AppPath Dir -> App m (Path Abs Dir)
|
|
RenderStdOut :: (HasAnsiBackend a, HasTextBackend a) => a -> App m ()
|
|
Say :: Text -> App m ()
|
|
SayRaw :: ByteString -> App m ()
|
|
|
|
data RunAppIOArgs = RunAppIOArgs
|
|
{ _runAppIOArgsGlobalOptions :: GlobalOptions,
|
|
_runAppIOArgsRoot :: Root
|
|
}
|
|
|
|
makeSem ''App
|
|
makeLenses ''RunAppIOArgs
|
|
|
|
runAppIO ::
|
|
forall r a.
|
|
(Members '[Embed IO, TaggedLock] r) =>
|
|
RunAppIOArgs ->
|
|
Sem (App ': r) a ->
|
|
Sem r a
|
|
runAppIO args = evalSingletonCache (readPackageRootIO root) . reAppIO args
|
|
where
|
|
root = args ^. runAppIOArgsRoot
|
|
|
|
reAppIO ::
|
|
forall r a.
|
|
(Members '[Embed IO, TaggedLock] r) =>
|
|
RunAppIOArgs ->
|
|
Sem (App ': r) a ->
|
|
Sem (SCache Package ': r) a
|
|
reAppIO args@RunAppIOArgs {..} =
|
|
reinterpret $ \case
|
|
AskPackageGlobal -> return (_runAppIOArgsRoot ^. rootPackageType `elem` [GlobalStdlib, GlobalPackageDescription, GlobalPackageBase])
|
|
FromAppPathFile p -> embed (prepathToAbsFile invDir (p ^. pathPath))
|
|
GetMainFile m -> getMainFile' m
|
|
FromAppPathDir p -> liftIO (prepathToAbsDir invDir (p ^. pathPath))
|
|
RenderStdOut t
|
|
| _runAppIOArgsGlobalOptions ^. globalOnlyErrors -> return ()
|
|
| otherwise -> embed $ do
|
|
sup <- Ansi.hSupportsANSIColor stdout
|
|
renderIO (not (_runAppIOArgsGlobalOptions ^. globalNoColors) && sup) t
|
|
AskGlobalOptions -> return _runAppIOArgsGlobalOptions
|
|
AskPackage -> getPkg
|
|
AskArgs -> return args
|
|
AskRoot -> return _runAppIOArgsRoot
|
|
AskInvokeDir -> return invDir
|
|
AskPkgDir -> return (_runAppIOArgsRoot ^. rootRootDir)
|
|
AskBuildDir -> return (resolveAbsBuildDir (_runAppIOArgsRoot ^. rootRootDir) (_runAppIOArgsRoot ^. rootBuildDir))
|
|
Say t
|
|
| g ^. globalOnlyErrors -> return ()
|
|
| otherwise -> putStrLn t
|
|
PrintJuvixError e -> do
|
|
printErr e
|
|
ExitJuvixError e -> do
|
|
printErr e
|
|
embed exitFailure
|
|
ExitMsg exitCode t -> exitMsg' (exitWith exitCode) t
|
|
ExitFailMsg t -> exitMsg' exitFailure t
|
|
SayRaw b -> embed (ByteString.putStr b)
|
|
where
|
|
getPkg :: (Members '[SCache Package] r') => Sem r' Package
|
|
getPkg = cacheSingletonGet
|
|
|
|
exitMsg' :: (Members '[Embed IO] r') => IO x -> Text -> Sem r' x
|
|
exitMsg' onExit t = liftIO (putStrLn t >> hFlush stdout >> onExit)
|
|
|
|
getMainFile' :: (Members '[SCache Package, Embed IO] r') => Maybe (AppPath File) -> Sem r' (Path Abs File)
|
|
getMainFile' = \case
|
|
Just p -> embed (prepathToAbsFile invDir (p ^. pathPath))
|
|
Nothing -> do
|
|
pkg <- getPkg
|
|
case pkg ^. packageMain of
|
|
Just p -> embed (prepathToAbsFile invDir p)
|
|
Nothing -> missingMainErr
|
|
|
|
missingMainErr :: (Members '[Embed IO] r') => Sem r' x
|
|
missingMainErr =
|
|
exitMsg'
|
|
exitFailure
|
|
( "A path to the main file must be given in the CLI or specified in the `main` field of the "
|
|
<> pack (toFilePath juvixYamlFile)
|
|
<> " file"
|
|
)
|
|
invDir = _runAppIOArgsRoot ^. rootInvokeDir
|
|
g :: GlobalOptions
|
|
g = _runAppIOArgsGlobalOptions
|
|
printErr e =
|
|
embed $ hPutStrLn stderr $ run $ runReader (project' @GenericOptions g) $ Error.render (not (_runAppIOArgsGlobalOptions ^. globalNoColors)) (g ^. globalOnlyErrors) e
|
|
|
|
getEntryPoint' :: (Members '[Embed IO, TaggedLock] r) => RunAppIOArgs -> AppPath File -> Sem r EntryPoint
|
|
getEntryPoint' RunAppIOArgs {..} inputFile = do
|
|
let opts = _runAppIOArgsGlobalOptions
|
|
root = _runAppIOArgsRoot
|
|
estdin <-
|
|
if
|
|
| opts ^. globalStdin -> Just <$> liftIO getContents
|
|
| otherwise -> return Nothing
|
|
set entryPointStdin estdin <$> entryPointFromGlobalOptionsPre root (inputFile ^. pathPath) opts
|
|
|
|
runPipelineEither :: (Members '[Embed IO, TaggedLock, App] r) => AppPath File -> Sem (PipelineEff r) a -> Sem r (Either JuvixError (ResolverState, PipelineResult a))
|
|
runPipelineEither input_ p = do
|
|
args <- askArgs
|
|
entry <- getEntryPoint' args input_
|
|
runIOEither entry p
|
|
|
|
runPipelineSetupEither :: (Members '[Embed IO, TaggedLock, App] r) => Sem (PipelineEff' r) a -> Sem r (Either JuvixError (ResolverState, a))
|
|
runPipelineSetupEither p = do
|
|
args <- askArgs
|
|
entry <- getEntryPointStdin' args
|
|
runIOEitherPipeline entry p
|
|
|
|
getEntryPointStdin' :: (Members '[Embed IO, TaggedLock] r) => RunAppIOArgs -> Sem r EntryPoint
|
|
getEntryPointStdin' RunAppIOArgs {..} = do
|
|
let opts = _runAppIOArgsGlobalOptions
|
|
root = _runAppIOArgsRoot
|
|
estdin <-
|
|
if
|
|
| opts ^. globalStdin -> Just <$> liftIO getContents
|
|
| otherwise -> return Nothing
|
|
set entryPointStdin estdin <$> entryPointFromGlobalOptionsNoFile root opts
|
|
|
|
someBaseToAbs' :: (Members '[App] r) => SomeBase a -> Sem r (Path Abs a)
|
|
someBaseToAbs' f = do
|
|
r <- askInvokeDir
|
|
return (someBaseToAbs r f)
|
|
|
|
filePathToAbs :: (Members '[Embed IO, App] r) => Prepath FileOrDir -> Sem r (Either (Path Abs File) (Path Abs Dir))
|
|
filePathToAbs fp = do
|
|
invokeDir <- askInvokeDir
|
|
embed (fromPreFileOrDir invokeDir fp)
|
|
|
|
askGenericOptions :: (Members '[App] r) => Sem r GenericOptions
|
|
askGenericOptions = project <$> askGlobalOptions
|
|
|
|
getEntryPoint :: (Members '[Embed IO, App, TaggedLock] r) => AppPath File -> Sem r EntryPoint
|
|
getEntryPoint inputFile = do
|
|
_runAppIOArgsGlobalOptions <- askGlobalOptions
|
|
_runAppIOArgsRoot <- askRoot
|
|
getEntryPoint' (RunAppIOArgs {..}) inputFile
|
|
|
|
getEntryPointStdin :: (Members '[Embed IO, App, TaggedLock] r) => Sem r EntryPoint
|
|
getEntryPointStdin = do
|
|
_runAppIOArgsGlobalOptions <- askGlobalOptions
|
|
_runAppIOArgsRoot <- askRoot
|
|
getEntryPointStdin' (RunAppIOArgs {..})
|
|
|
|
runPipelineTermination :: (Members '[Embed IO, App, TaggedLock] r) => AppPath File -> Sem (Termination ': PipelineEff r) a -> Sem r (PipelineResult a)
|
|
runPipelineTermination input_ p = do
|
|
r <- runPipelineEither input_ (evalTermination iniTerminationState p)
|
|
case r of
|
|
Left err -> exitJuvixError err
|
|
Right res -> return (snd res)
|
|
|
|
runPipeline :: (Members '[App, Embed IO, TaggedLock] r) => AppPath File -> Sem (PipelineEff r) a -> Sem r a
|
|
runPipeline input_ p = do
|
|
r <- runPipelineEither input_ p
|
|
case r of
|
|
Left err -> exitJuvixError err
|
|
Right res -> return (snd res ^. pipelineResult)
|
|
|
|
runPipelineHtml :: (Members '[App, Embed IO, TaggedLock] r) => Bool -> AppPath File -> Sem r (InternalTypedResult, [InternalTypedResult])
|
|
runPipelineHtml bNonRecursive input_
|
|
| bNonRecursive = do
|
|
r <- runPipeline input_ upToInternalTyped
|
|
return (r, [])
|
|
| otherwise = do
|
|
args <- askArgs
|
|
entry <- getEntryPoint' args input_
|
|
r <- runPipelineHtmlEither entry
|
|
case r of
|
|
Left err -> exitJuvixError err
|
|
Right res -> return res
|
|
|
|
runPipelineEntry :: (Members '[App, Embed IO, TaggedLock] r) => EntryPoint -> Sem (PipelineEff r) a -> Sem r a
|
|
runPipelineEntry entry p = do
|
|
r <- runIOEither entry p
|
|
case r of
|
|
Left err -> exitJuvixError err
|
|
Right res -> return (snd res ^. pipelineResult)
|
|
|
|
runPipelineSetup :: (Members '[App, Embed IO, TaggedLock] r) => Sem (PipelineEff' r) a -> Sem r a
|
|
runPipelineSetup p = do
|
|
r <- runPipelineSetupEither p
|
|
case r of
|
|
Left err -> exitJuvixError err
|
|
Right res -> return (snd res)
|
|
|
|
newline :: (Member App r) => Sem r ()
|
|
newline = say ""
|
|
|
|
printSuccessExit :: (Member App r) => Text -> Sem r a
|
|
printSuccessExit = exitMsg ExitSuccess
|
|
|
|
printFailureExit :: (Member App r) => Text -> Sem r a
|
|
printFailureExit = exitMsg (ExitFailure 1)
|
|
|
|
getRight :: (Members '[App] r, AppError e) => Either e a -> Sem r a
|
|
getRight = either appError return
|
|
|
|
instance AppError Text where
|
|
appError = printFailureExit
|
|
|
|
instance AppError JuvixError where
|
|
appError = exitJuvixError
|
|
|
|
class AppError e where
|
|
appError :: (Members '[App] r) => e -> Sem r a
|