1
1
mirror of https://github.com/anoma/juvix.git synced 2024-09-17 19:47:45 +03:00
juvix/app/Evaluator.hs
Łukasz Czajka dcea0bbecb
Add field element type (#2659)
* Closes #2571
* It is reasonable to finish this PR before tackling #2562, because the
field element type is the primary data type in Cairo.
* Depends on #2653

Checklist
---------

- [x] Add field type and operations to intermediate representations
(JuvixCore, JuvixTree, JuvixAsm, JuvixReg).
- [x] Add CLI option to choose field size.
- [x] Add frontend field builtins.
- [x] Automatic conversion of integer literals to field elements.
- [x] Juvix standard library support for fields.
- [x] Check if field size matches when loading a stored module.
- [x] Update the Cairo Assembly (CASM) interpreter to use the field type
instead of integer type.
- [x] Add field type to VampIR backend.
- [x] Tests

---------

Co-authored-by: Jan Mas Rovira <janmasrovira@gmail.com>
2024-02-27 14:54:43 +01:00

70 lines
2.4 KiB
Haskell

module Evaluator where
import App
import CommonOptions
import Juvix.Compiler.Core 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.Normalizer
import Juvix.Compiler.Core.Pretty qualified as Core
import Juvix.Compiler.Core.Transformation.DisambiguateNames qualified as Core
data EvalOptions = EvalOptions
{ _evalInputFile :: AppPath File,
_evalNoIO :: Bool,
_evalNoDisambiguate :: Bool,
_evalPrintValues :: Bool
}
makeLenses ''EvalOptions
evalAndPrint ::
forall r a b.
(Members '[EmbedIO, App] r, CanonicalProjection a EvalOptions, CanonicalProjection b Core.CoreOptions, CanonicalProjection a Core.Options) =>
b ->
a ->
Core.InfoTable ->
Core.Node ->
Sem r ()
evalAndPrint gopts opts tab node = do
loc <- defaultLoc
r <- Core.doEval (Just $ project gopts ^. Core.optFieldSize) (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 (Core.moduleFromInfoTable tab) node'
where
defaultLoc :: Sem r Interval
defaultLoc = singletonInterval . mkInitialLoc <$> fromAppPathFile f
f :: AppPath File
f = project opts ^. evalInputFile
normalizeAndPrint ::
forall r a b.
(Members '[EmbedIO, App] r, CanonicalProjection a EvalOptions, CanonicalProjection b Core.CoreOptions, CanonicalProjection a Core.Options) =>
b ->
a ->
Core.InfoTable ->
Core.Node ->
Sem r ()
normalizeAndPrint gopts opts tab node =
let node' = normalize (project gopts ^. Core.optFieldSize) (Core.moduleFromInfoTable 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 (Core.moduleFromInfoTable tab) node'
renderStdOut (Core.ppOut opts node'')
putStrLn ""