1
1
mirror of https://github.com/anoma/juvix.git synced 2025-01-04 13:42:04 +03:00
juvix/app/Commands/Dev/Core/Read.hs
Łukasz Czajka c9b8cdd5e9
Pattern matching compilation (#1874)
This implements a basic version of the algorithm from: Luc Maranget,
[Compiling pattern matching to good decision
trees](http://moscova.inria.fr/~maranget/papers/ml05e-maranget.pdf). No
heuristics are used - the first column is always chosen.

* Closes #1798 
* Closes #1225 
* Closes #1926 
* Adds a global `--no-coverage` option which turns off coverage checking
in favour of generating runtime failures
* Changes the representation of Match patterns in JuvixCore to achieve a
more streamlined implementation
* Adds options to the Core pipeline
2023-03-27 10:42:27 +02:00

46 lines
2.0 KiB
Haskell

module Commands.Dev.Core.Read where
import Commands.Base
import Commands.Dev.Core.Read.Options
import Evaluator qualified as Eval
import Juvix.Compiler.Core.Options qualified as Core
import Juvix.Compiler.Core.Pretty qualified as Pretty
import Juvix.Compiler.Core.Scoper qualified as Scoper
import Juvix.Compiler.Core.Transformation qualified as Core
import Juvix.Compiler.Core.Transformation.DisambiguateNames qualified as Core
import Juvix.Compiler.Core.Translation.FromSource qualified as Core
runCommand ::
forall r a.
( Members '[Embed IO, App] r,
CanonicalProjection a Eval.EvalOptions,
CanonicalProjection a Pretty.Options,
CanonicalProjection a CoreReadOptions
) =>
a ->
Sem r ()
runCommand opts = do
gopts <- askGlobalOptions
inputFile :: Path Abs File <- someBaseToAbs' sinputFile
s' <- embed . readFile . toFilePath $ inputFile
tab <- getRight (mapLeft JuvixError (Core.runParserMain inputFile Core.emptyInfoTable s'))
let r = run $ runReader (project @GlobalOptions @Core.CoreOptions gopts) $ runError @JuvixError $ Core.applyTransformations (project opts ^. coreReadTransformations) tab
tab0 <- getRight $ mapLeft JuvixError r
let tab' = if project opts ^. coreReadNoDisambiguate then tab0 else Core.disambiguateNames tab0
embed (Scoper.scopeTrace tab')
unless (project opts ^. coreReadNoPrint) $ do
renderStdOut (Pretty.ppOut opts tab')
whenJust (tab' ^. Core.infoMain) $ \sym -> doEval tab' (fromJust $ tab' ^. Core.identContext . at sym)
where
doEval :: Core.InfoTable -> Core.Node -> Sem r ()
doEval tab' node =
if
| project opts ^. coreReadEval -> do
embed (putStrLn "--------------------------------")
embed (putStrLn "| Eval |")
embed (putStrLn "--------------------------------")
Eval.evalAndPrint opts tab' node
| otherwise -> return ()
sinputFile :: SomeBase File
sinputFile = project opts ^. coreReadInputFile . pathPath