1
1
mirror of https://github.com/anoma/juvix.git synced 2024-12-15 01:52:11 +03:00
juvix/app/Commands/Dev/Core/Eval.hs
Paul Cadman b6f1ecac73
Add --show-de-bruijn to core eval command (#1540)
This option was removed as part of one of the cli refactors
2022-09-15 15:26:02 +01:00

49 lines
1.8 KiB
Haskell

module Commands.Dev.Core.Eval where
import Commands.Base
import Commands.Dev.Core.Eval.Options
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.Pretty qualified as Core
import Juvix.Compiler.Core.Translation.FromSource qualified as Core
import Text.Megaparsec.Pos qualified as M
doEval ::
forall r.
Members '[Embed IO, App] 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 (tab ^. Core.identContext) [] node)
| otherwise = embed $ Core.catchEvalErrorIO loc (Core.evalIO (tab ^. Core.identContext) [] node)
runCommand :: forall r. Members '[Embed IO, App] r => CoreEvalOptions -> Sem r ()
runCommand opts = do
s <- embed (readFile f)
case Core.runParser "" f Core.emptyInfoTable s of
Left err -> exitJuvixError (JuvixError err)
Right (tab, Just node) -> do
r <- doEval (opts ^. coreEvalNoIO) defaultLoc 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 "")
Right (_, Nothing) -> return ()
where
defaultLoc :: Interval
defaultLoc = singletonInterval (mkLoc f 0 (M.initialPos f))
f :: FilePath
f = opts ^. coreEvalInputFile . pathPath