1
1
mirror of https://github.com/anoma/juvix.git synced 2024-12-15 01:52:11 +03:00
juvix/app/Evaluator.hs

80 lines
2.5 KiB
Haskell
Raw Normal View History

module Evaluator where
import App
import CommonOptions
import Juvix.Compiler.Core.Data.InfoTable qualified as Core
import Juvix.Compiler.Core.Error qualified as Core
import Juvix.Compiler.Core.Evaluator qualified as Core
import Juvix.Compiler.Core.Extra.Base qualified as Core
import Juvix.Compiler.Core.Extra.Value qualified as Core
import Juvix.Compiler.Core.Info qualified as Info
import Juvix.Compiler.Core.Info.NoDisplayInfo qualified as Info
import Juvix.Compiler.Core.Language qualified as Core
import Juvix.Compiler.Core.Normalizer
import Juvix.Compiler.Core.Pretty qualified as Core
import Juvix.Compiler.Core.Transformation.DisambiguateNames qualified as Core
data EvalOptions = EvalOptions
2022-12-20 15:05:40 +03:00
{ _evalInputFile :: AppPath File,
_evalNoIO :: Bool,
_evalNoDisambiguate :: Bool,
_evalPrintValues :: Bool
}
makeLenses ''EvalOptions
doEvalIO ::
Bool ->
Interval ->
Core.InfoTable ->
Core.Node ->
IO (Either Core.CoreError Core.Node)
Use a Juvix source file to define a package (#2434) Depends on: * ~~https://github.com/anoma/juvix/pull/2459~~ * https://github.com/anoma/juvix/pull/2462 This PR is part of a series implementing: * https://github.com/anoma/juvix/issues/2336 This PR adds the package file loading function, including a file evaluation effect. It integrates this with the existing `readPackage` function and adds tests / smoke tests. ## Package.juvix format Instead of `juvix.yaml` (which is still supported currently) users can now place a `Package.juvix` file in the root of their project. The simplest `Package.juvix` file you can write is: ``` module Package; import PackageDescription open; package : Package := defaultPackage; ``` The [PackageDescription](https://github.com/anoma/juvix/blob/35b2f618f093895f32929ac0f2c0affcdab8d627/include/package/PackageDescription.juvix) module defines the `Package` type. Users can use "go-to definition" in their IDE from the Package file to see the documentation and definitions. Users may also import `Stdlib.Prelude` in their Package file. This is loaded from the global project. No other module imports are supported. Notes: * If a directory contains both `Package.juvix` and `juvix.yaml` then `Package.juvix` is used in preference. ## Default stdlib dependency The `Dependency` type has a constructor called `defaultStdlib`. This means that any project can use the compiler builtin standard library dependency. With `juvix.yaml` this dependency is only available when the `dependencies` field is unspecified. ``` module Package; import PackageDescription open; package : Package := defaultPackage { dependencies := [defaultStdlib] }; ``` ## Validation As well as the standard type checking validation that the Juvix compiler provides additional validation is made on the file. * The Package module must contain the identifier `package` and it must have type `Package` that's obtained from the global `PackageDescription` module. * Every dependency specified in the Package.juvix must be unique. * Closes https://github.com/anoma/juvix/issues/2336 ## Examples ### Package with name and version ``` module Package; import PackageDescription open; package : Package := defaultPackage {name := "a-package"; version := mkVersion 0 1 0}; ``` ### Package with GitHub dependency ``` module Package; import PackageDescription open; package : Package := defaultPackage {name := "a-package"; version := mkVersion 0 1 0; dependencies := [defaultStdlib; github (org := "anoma"; repo := "juvix-containers"; ref := "v0.7.1")]}; ``` ## Package with main and buildDir fields ``` module Package; import Stdlib.Prelude open; import PackageDescription open; package : Package := defaultPackage {name := "a-package"; version := mkVersion 0 1 0; dependencies := [defaultStdlib; github (org := "anoma"; repo := "juvix-containers"; ref := "v0.7.1")]; buildDir := just "/tmp/build"; main := just "HelloWorld.juvix" }; ```
2023-10-27 14:35:20 +03:00
doEvalIO noIO i tab node = runM (Core.doEval noIO i tab node)
evalAndPrint ::
forall r a.
(Members '[Embed IO, App] r, CanonicalProjection a EvalOptions, CanonicalProjection a Core.Options) =>
a ->
Core.InfoTable ->
Core.Node ->
Sem r ()
evalAndPrint opts tab node = do
loc <- defaultLoc
Use a Juvix source file to define a package (#2434) Depends on: * ~~https://github.com/anoma/juvix/pull/2459~~ * https://github.com/anoma/juvix/pull/2462 This PR is part of a series implementing: * https://github.com/anoma/juvix/issues/2336 This PR adds the package file loading function, including a file evaluation effect. It integrates this with the existing `readPackage` function and adds tests / smoke tests. ## Package.juvix format Instead of `juvix.yaml` (which is still supported currently) users can now place a `Package.juvix` file in the root of their project. The simplest `Package.juvix` file you can write is: ``` module Package; import PackageDescription open; package : Package := defaultPackage; ``` The [PackageDescription](https://github.com/anoma/juvix/blob/35b2f618f093895f32929ac0f2c0affcdab8d627/include/package/PackageDescription.juvix) module defines the `Package` type. Users can use "go-to definition" in their IDE from the Package file to see the documentation and definitions. Users may also import `Stdlib.Prelude` in their Package file. This is loaded from the global project. No other module imports are supported. Notes: * If a directory contains both `Package.juvix` and `juvix.yaml` then `Package.juvix` is used in preference. ## Default stdlib dependency The `Dependency` type has a constructor called `defaultStdlib`. This means that any project can use the compiler builtin standard library dependency. With `juvix.yaml` this dependency is only available when the `dependencies` field is unspecified. ``` module Package; import PackageDescription open; package : Package := defaultPackage { dependencies := [defaultStdlib] }; ``` ## Validation As well as the standard type checking validation that the Juvix compiler provides additional validation is made on the file. * The Package module must contain the identifier `package` and it must have type `Package` that's obtained from the global `PackageDescription` module. * Every dependency specified in the Package.juvix must be unique. * Closes https://github.com/anoma/juvix/issues/2336 ## Examples ### Package with name and version ``` module Package; import PackageDescription open; package : Package := defaultPackage {name := "a-package"; version := mkVersion 0 1 0}; ``` ### Package with GitHub dependency ``` module Package; import PackageDescription open; package : Package := defaultPackage {name := "a-package"; version := mkVersion 0 1 0; dependencies := [defaultStdlib; github (org := "anoma"; repo := "juvix-containers"; ref := "v0.7.1")]}; ``` ## Package with main and buildDir fields ``` module Package; import Stdlib.Prelude open; import PackageDescription open; package : Package := defaultPackage {name := "a-package"; version := mkVersion 0 1 0; dependencies := [defaultStdlib; github (org := "anoma"; repo := "juvix-containers"; ref := "v0.7.1")]; buildDir := just "/tmp/build"; main := just "HelloWorld.juvix" }; ```
2023-10-27 14:35:20 +03:00
r <- Core.doEval (project opts ^. evalNoIO) loc tab node
case r of
Left err -> exitJuvixError (JuvixError err)
Right node'
| Info.member Info.kNoDisplayInfo (Core.getInfo node') ->
return ()
Right node'
| project opts ^. evalPrintValues -> do
renderStdOut (Core.ppOut opts (Core.toValue tab node'))
newline
| otherwise -> do
renderStdOut (Core.ppOut opts node'')
newline
where
node'' = if project opts ^. evalNoDisambiguate then node' else Core.disambiguateNodeNames tab node'
where
defaultLoc :: Sem r Interval
defaultLoc = singletonInterval . mkInitialLoc <$> fromAppPathFile f
f :: AppPath File
f = project opts ^. evalInputFile
normalizeAndPrint ::
forall r a.
(Members '[Embed IO, App] r, CanonicalProjection a EvalOptions, CanonicalProjection a Core.Options) =>
a ->
Core.InfoTable ->
Core.Node ->
Sem r ()
normalizeAndPrint opts tab node =
let node' = normalize tab node
in if
| Info.member Info.kNoDisplayInfo (Core.getInfo node') ->
return ()
| otherwise -> do
let node'' = if project opts ^. evalNoDisambiguate then node' else Core.disambiguateNodeNames tab node'
renderStdOut (Core.ppOut opts node'')
embed (putStrLn "")