1
1
mirror of https://github.com/github/semantic.git synced 2024-12-03 00:16:52 +03:00
semantic/bench/Main.hs

51 lines
2.5 KiB
Haskell
Raw Normal View History

{-# LANGUAGE DataKinds, FlexibleContexts, TypeFamilies, TypeApplications #-}
2018-03-08 03:34:20 +03:00
module Main where
import Control.Monad
import Criterion.Main
import qualified Data.Language as Language
import Data.Proxy
import Parsing.Parser
import Semantic.Config (defaultOptions)
import Semantic.Task (withOptions)
import Semantic.Util hiding (evalRubyProject, evalPythonProject, evaluateProject)
-- Duplicating this stuff from Util to shut off the logging
2018-08-14 01:42:42 +03:00
evalRubyProject = justEvaluating <=< evaluateProject (Proxy :: Proxy 'Language.Ruby) rubyParser
evalPythonProject = justEvaluating <=< evaluateProject (Proxy :: Proxy 'Language.Python) pythonParser
2018-08-14 01:42:42 +03:00
evaluateProject proxy parser paths = withOptions defaultOptions $ \ config logger statter ->
evaluateProject' (TaskConfig config logger statter) proxy parser paths
2018-03-08 03:34:20 +03:00
2018-03-08 21:18:36 +03:00
-- We use `fmap show` to ensure that all the parts of the result of evaluation are
-- evaluated themselves. While an NFData instance is the most morally correct way
-- to do this, I'm reluctant to add NFData instances to every single datatype in the
-- project—coercing the result into a string will suffice, though it throws off the
-- memory allocation results a bit.
2018-03-08 03:34:20 +03:00
pyEval :: FilePath -> Benchmarkable
pyEval p = whnfIO . fmap show . evalPythonProject $ ["bench/bench-fixtures/python/" <> p]
2018-03-08 03:34:20 +03:00
2018-03-08 03:47:23 +03:00
rbEval :: FilePath -> Benchmarkable
rbEval p = whnfIO . fmap show . evalRubyProject $ ["bench/bench-fixtures/ruby/" <> p]
pyCall :: FilePath -> Benchmarkable
2018-08-14 01:42:42 +03:00
pyCall p = whnfIO $ callGraphProject pythonParser (Proxy @'Language.Python) defaultOptions ["bench/bench-fixtures/python/" <> p]
rbCall :: FilePath -> Benchmarkable
2018-08-14 01:42:42 +03:00
rbCall p = whnfIO $ callGraphProject rubyParser (Proxy @'Language.Ruby) defaultOptions ["bench/bench-fixtures/ruby/" <> p]
2018-03-08 03:34:20 +03:00
main :: IO ()
2018-03-08 03:47:23 +03:00
main = defaultMain
[ bgroup "python" [ bench "assignment" $ pyEval "simple-assignment.py"
2018-03-12 17:51:07 +03:00
, bench "function def" $ pyEval "function-definition.py"
, bench "if + function calls" $ pyEval "if-statement-functions.py"
, bench "call graph" $ pyCall "if-statement-functions.py"
2018-03-12 17:51:07 +03:00
]
2018-03-08 03:47:23 +03:00
, bgroup "ruby" [ bench "assignment" $ rbEval "simple-assignment.rb"
, bench "function def" $ rbEval "function-definition.rb"
, bench "if + function calls" $ rbEval "if-statement-functions.rb"
, bench "call graph" $ rbCall "if-statement-functions.rb"
2018-03-08 03:47:23 +03:00
]
2018-03-08 03:34:20 +03:00
]