1
1
mirror of https://github.com/anoma/juvix.git synced 2024-12-04 06:23:13 +03:00
juvix/app/Evaluator.hs
Łukasz Czajka 336a934d18
Normalization by Evaluation (#2038)
* Closes #2032.
* Adds the `juvix dev core normalize` command.
* Adds the `:n` command in JuvixCore REPL.
* Adds the `--normalize` flag to `juvix dev core read` and `juvix dev
core from-concrete`.
* Adds `pipeline-normalize` which denotes pipeline steps necessary
before normalization.
* Adds normalization tests in `tests/VampIR/positive/Core`.
2023-05-15 18:01:40 +02:00

86 lines
2.7 KiB
Haskell

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.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
{ _evalInputFile :: AppPath File,
_evalNoIO :: Bool,
_evalNoDisambiguate :: Bool
}
makeLenses ''EvalOptions
doEval ::
forall r.
(Members '[Embed IO] r) =>
Bool ->
Interval ->
Core.InfoTable ->
Core.Node ->
Sem r (Either Core.CoreError Core.Node)
doEval noIO loc tab node
| noIO = embed $ Core.catchEvalError loc (Core.eval stderr (tab ^. Core.identContext) [] node)
| otherwise = embed $ Core.catchEvalErrorIO loc (Core.evalIO (tab ^. Core.identContext) [] node)
doEvalIO ::
Bool ->
Interval ->
Core.InfoTable ->
Core.Node ->
IO (Either Core.CoreError Core.Node)
doEvalIO noIO i tab node = runM (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
r <- 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' -> do
renderStdOut (Core.ppOut opts node'')
embed (putStrLn "")
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 "")