mirror of
https://github.com/anoma/juvix.git
synced 2024-12-13 19:49:20 +03:00
3a4cbc742d
The following benchmark compares juvix 0.6.0 with polysemy and a new version (implemented in this pr) which replaces polysemy by effectful. # Typecheck standard library without caching ``` hyperfine --warmup 2 --prepare 'juvix-polysemy clean' 'juvix-polysemy typecheck Stdlib/Prelude.juvix' 'juvix-effectful typecheck Stdlib/Prelude.juvix' Benchmark 1: juvix-polysemy typecheck Stdlib/Prelude.juvix Time (mean ± σ): 3.924 s ± 0.143 s [User: 3.787 s, System: 0.084 s] Range (min … max): 3.649 s … 4.142 s 10 runs Benchmark 2: juvix-effectful typecheck Stdlib/Prelude.juvix Time (mean ± σ): 2.558 s ± 0.074 s [User: 2.430 s, System: 0.084 s] Range (min … max): 2.403 s … 2.646 s 10 runs Summary juvix-effectful typecheck Stdlib/Prelude.juvix ran 1.53 ± 0.07 times faster than juvix-polysemy typecheck Stdlib/Prelude.juvix ``` # Typecheck standard library with caching ``` hyperfine --warmup 1 'juvix-effectful typecheck Stdlib/Prelude.juvix' 'juvix-polysemy typecheck Stdlib/Prelude.juvix' --min-runs 20 Benchmark 1: juvix-effectful typecheck Stdlib/Prelude.juvix Time (mean ± σ): 1.194 s ± 0.068 s [User: 0.979 s, System: 0.211 s] Range (min … max): 1.113 s … 1.307 s 20 runs Benchmark 2: juvix-polysemy typecheck Stdlib/Prelude.juvix Time (mean ± σ): 1.237 s ± 0.083 s [User: 0.997 s, System: 0.231 s] Range (min … max): 1.061 s … 1.476 s 20 runs Summary juvix-effectful typecheck Stdlib/Prelude.juvix ran 1.04 ± 0.09 times faster than juvix-polysemy typecheck Stdlib/Prelude.juvix ```
99 lines
3.5 KiB
Haskell
99 lines
3.5 KiB
Haskell
module Reg.Run.Base where
|
|
|
|
import Base
|
|
import Juvix.Compiler.Reg.Data.InfoTable
|
|
import Juvix.Compiler.Reg.Error
|
|
import Juvix.Compiler.Reg.Interpreter
|
|
import Juvix.Compiler.Reg.Pretty
|
|
import Juvix.Compiler.Reg.Transformation
|
|
import Juvix.Compiler.Reg.Translation.FromSource
|
|
import Juvix.Data.PPOutput
|
|
|
|
runAssertion :: Handle -> Symbol -> InfoTable -> IO ()
|
|
runAssertion hout sym tab = do
|
|
r' <- doRun hout tab (lookupFunInfo tab sym)
|
|
case r' of
|
|
Left err -> do
|
|
hClose hout
|
|
assertFailure (show (pretty err))
|
|
Right value' -> do
|
|
case value' of
|
|
ValVoid -> return ()
|
|
_ -> hPutStrLn hout (ppPrint tab value')
|
|
|
|
regRunAssertion' :: InfoTable -> Path Abs File -> (String -> IO ()) -> Assertion
|
|
regRunAssertion' = regRunAssertionParam' runAssertion
|
|
|
|
regRunAssertionParam' :: (Handle -> Symbol -> InfoTable -> IO ()) -> InfoTable -> Path Abs File -> (String -> IO ()) -> Assertion
|
|
regRunAssertionParam' interpretFun tab expectedFile step = do
|
|
case tab ^. infoMainFunction of
|
|
Just sym -> do
|
|
withTempDir'
|
|
( \dirPath -> do
|
|
let outputFile = dirPath <//> $(mkRelFile "out.out")
|
|
hout <- openFile (toFilePath outputFile) WriteMode
|
|
step "Interpret"
|
|
interpretFun hout sym tab
|
|
hClose hout
|
|
actualOutput <- readFile outputFile
|
|
step "Compare expected and actual program output"
|
|
expected <- readFile expectedFile
|
|
assertEqDiffText ("Check: RUN output = " <> toFilePath expectedFile) actualOutput expected
|
|
)
|
|
Nothing -> assertFailure "no 'main' function"
|
|
|
|
regRunAssertion :: Path Abs File -> Path Abs File -> [TransformationId] -> (InfoTable -> Assertion) -> (String -> IO ()) -> Assertion
|
|
regRunAssertion = regRunAssertionParam runAssertion
|
|
|
|
regRunAssertionParam :: (Handle -> Symbol -> InfoTable -> IO ()) -> Path Abs File -> Path Abs File -> [TransformationId] -> (InfoTable -> Assertion) -> (String -> IO ()) -> Assertion
|
|
regRunAssertionParam interpretFun mainFile expectedFile trans testTrans step = do
|
|
step "Parse"
|
|
r <- parseFile mainFile
|
|
case r of
|
|
Left err -> assertFailure (show (pretty err))
|
|
Right tab0 -> do
|
|
unless (null trans) $
|
|
step "Transform"
|
|
case run $ runError @JuvixError $ applyTransformations trans tab0 of
|
|
Left err -> assertFailure (show (pretty (fromJuvixError @GenericError err)))
|
|
Right tab -> do
|
|
testTrans tab
|
|
regRunAssertionParam' interpretFun tab expectedFile step
|
|
|
|
regRunErrorAssertion :: Path Abs File -> (String -> IO ()) -> Assertion
|
|
regRunErrorAssertion mainFile step = do
|
|
step "Parse"
|
|
r <- parseFile mainFile
|
|
case r of
|
|
Left _ -> assertBool "" True
|
|
Right tab ->
|
|
case tab ^. infoMainFunction of
|
|
Just sym -> do
|
|
withTempDir'
|
|
( \dirPath -> do
|
|
let outputFile = dirPath <//> $(mkRelFile "out.out")
|
|
hout <- openFile (toFilePath outputFile) WriteMode
|
|
step "Interpret"
|
|
r' <- doRun hout tab (lookupFunInfo tab sym)
|
|
hClose hout
|
|
case r' of
|
|
Left _ -> assertBool "" True
|
|
Right _ -> assertFailure "no error"
|
|
)
|
|
Nothing -> assertBool "" True
|
|
|
|
parseFile :: Path Abs File -> IO (Either MegaparsecError InfoTable)
|
|
parseFile f = do
|
|
s <- readFile f
|
|
return (runParser f s)
|
|
|
|
doRun ::
|
|
Handle ->
|
|
InfoTable ->
|
|
FunctionInfo ->
|
|
IO (Either RegError Val)
|
|
doRun hout tab funInfo =
|
|
runM
|
|
. runError
|
|
$ runFunctionIO stdin hout tab [] funInfo
|