mirror of
https://github.com/github/semantic.git
synced 2025-01-02 04:10:29 +03:00
Merge pull request #2030 from github/serialize-test-queue-output
Serialize test queue output
This commit is contained in:
commit
38b48a8a0c
@ -37,6 +37,7 @@ module Semantic.Task
|
||||
-- * Interpreting
|
||||
, runTask
|
||||
, runTaskWithOptions
|
||||
, withOptions
|
||||
, runTaskWithConfig
|
||||
-- * Re-exports
|
||||
, Distribute
|
||||
@ -127,11 +128,12 @@ runTask = runTaskWithOptions defaultOptions
|
||||
|
||||
-- | Execute a 'TaskEff' with the passed 'Options', yielding its result value in 'IO'.
|
||||
runTaskWithOptions :: Options -> TaskEff a -> IO a
|
||||
runTaskWithOptions opts task = do
|
||||
config <- defaultConfig opts
|
||||
result <- withTelemetry config $ \(TelemetryQueues logger statter _) ->
|
||||
runTaskWithConfig config logger statter task
|
||||
either (die . displayException) pure result
|
||||
runTaskWithOptions opts task = withOptions opts (\ config logger statter -> runTaskWithConfig config logger statter task) >>= either (die . displayException) pure
|
||||
|
||||
withOptions :: Options -> (Config -> LogQueue -> StatQueue -> IO a) -> IO a
|
||||
withOptions options with = do
|
||||
config <- defaultConfig options
|
||||
withTelemetry config (\ (TelemetryQueues logger statter _) -> with config logger statter)
|
||||
|
||||
-- | Execute a 'TaskEff' yielding its result value in 'IO'.
|
||||
runTaskWithConfig :: Config -> LogQueue -> StatQueue -> TaskEff a -> IO (Either SomeException a)
|
||||
|
@ -7,6 +7,7 @@ import Prelude hiding (readFile)
|
||||
import Analysis.Abstract.Caching
|
||||
import Analysis.Abstract.Collecting
|
||||
import Control.Abstract
|
||||
import Control.Exception (displayException)
|
||||
import Control.Monad.Effect.Trace (runPrintingTrace)
|
||||
import Data.Abstract.Address
|
||||
import Data.Abstract.Evaluatable
|
||||
@ -27,9 +28,12 @@ import Language.Haskell.HsColour
|
||||
import Language.Haskell.HsColour.Colourise
|
||||
import Parsing.Parser
|
||||
import Prologue hiding (weaken)
|
||||
import Semantic.Config
|
||||
import Semantic.Graph
|
||||
import Semantic.IO as IO
|
||||
import Semantic.Task
|
||||
import Semantic.Telemetry (LogQueue, StatQueue)
|
||||
import System.Exit (die)
|
||||
import System.FilePath.Posix (takeDirectory)
|
||||
import Text.Show (showListWith)
|
||||
import Text.Show.Pretty (ppShow)
|
||||
@ -99,7 +103,12 @@ evalTypeScriptProject = justEvaluating <=< evaluateProject (Proxy :: Proxy 'Lang
|
||||
typecheckGoFile = checking <=< evaluateProjectWithCaching (Proxy :: Proxy 'Language.Go) goParser Language.Go
|
||||
|
||||
-- Evaluate a project consisting of the listed paths.
|
||||
evaluateProject proxy parser lang paths = runTaskWithOptions debugOptions $ do
|
||||
evaluateProject proxy parser lang paths = withOptions debugOptions $ \ config logger statter ->
|
||||
evaluateProject' (TaskConfig config logger statter) proxy parser lang paths
|
||||
|
||||
data TaskConfig = TaskConfig Config LogQueue StatQueue
|
||||
|
||||
evaluateProject' (TaskConfig config logger statter) proxy parser lang paths = either (die . displayException) pure <=< runTaskWithConfig config logger statter $ do
|
||||
blobs <- catMaybes <$> traverse readFile (flip File lang <$> paths)
|
||||
package <- fmap quieterm <$> parsePackage parser (Project (takeDirectory (maybe "/" fst (uncons paths))) blobs lang [])
|
||||
modules <- topologicalSort <$> runImportGraph proxy package
|
||||
@ -111,6 +120,7 @@ evaluateProject proxy parser lang paths = runTaskWithOptions debugOptions $ do
|
||||
(raiseHandler (runModules (ModuleTable.modulePaths (packageModules package)))
|
||||
(evaluate proxy id withTermSpans modules))))))
|
||||
|
||||
|
||||
evaluateProjectWithCaching proxy parser lang path = runTaskWithOptions debugOptions $ do
|
||||
project <- readProject Nothing path lang []
|
||||
package <- fmap quieterm <$> parsePackage parser project
|
||||
|
@ -8,8 +8,8 @@ import qualified Language.Go.Assignment as Go
|
||||
import SpecHelpers
|
||||
|
||||
|
||||
spec :: Spec
|
||||
spec = parallel $ do
|
||||
spec :: TaskConfig -> Spec
|
||||
spec config = parallel $ do
|
||||
describe "Go" $ do
|
||||
it "imports and wildcard imports" $ do
|
||||
(_, (heap, res)) <- evaluate ["main.go", "foo/foo.go", "bar/bar.go", "bar/rab.go"]
|
||||
@ -30,4 +30,4 @@ spec = parallel $ do
|
||||
where
|
||||
fixtures = "test/fixtures/go/analysis/"
|
||||
evaluate = evalGoProject . map (fixtures <>)
|
||||
evalGoProject = testEvaluating <=< evaluateProject (Proxy :: Proxy 'Language.Go) goParser Language.Go
|
||||
evalGoProject = testEvaluating <=< evaluateProject' config (Proxy :: Proxy 'Language.Go) goParser Language.Go
|
||||
|
@ -9,8 +9,8 @@ import qualified Language.PHP.Assignment as PHP
|
||||
import SpecHelpers
|
||||
|
||||
|
||||
spec :: Spec
|
||||
spec = parallel $ do
|
||||
spec :: TaskConfig -> Spec
|
||||
spec config = parallel $ do
|
||||
describe "PHP" $ do
|
||||
it "evaluates include and require" $ do
|
||||
(_, (heap, res)) <- evaluate ["main.php", "foo.php", "bar.php"]
|
||||
@ -42,4 +42,4 @@ spec = parallel $ do
|
||||
where
|
||||
fixtures = "test/fixtures/php/analysis/"
|
||||
evaluate = evalPHPProject . map (fixtures <>)
|
||||
evalPHPProject = testEvaluating <=< evaluateProject (Proxy :: Proxy 'Language.PHP) phpParser Language.PHP
|
||||
evalPHPProject = testEvaluating <=< evaluateProject' config (Proxy :: Proxy 'Language.PHP) phpParser Language.PHP
|
||||
|
@ -10,8 +10,8 @@ import qualified Data.Language as Language
|
||||
import SpecHelpers
|
||||
|
||||
|
||||
spec :: Spec
|
||||
spec = parallel $ do
|
||||
spec :: TaskConfig -> Spec
|
||||
spec config = parallel $ do
|
||||
describe "Python" $ do
|
||||
it "imports" $ do
|
||||
(_, (heap, res)) <- evaluate ["main.py", "a.py", "b/__init__.py", "b/c.py"]
|
||||
@ -60,4 +60,4 @@ spec = parallel $ do
|
||||
ns n = Just . Latest . Last . Just . Namespace n
|
||||
fixtures = "test/fixtures/python/analysis/"
|
||||
evaluate = evalPythonProject . map (fixtures <>)
|
||||
evalPythonProject = testEvaluating <=< evaluateProject (Proxy :: Proxy 'Language.Python) pythonParser Language.Python
|
||||
evalPythonProject = testEvaluating <=< evaluateProject' config (Proxy :: Proxy 'Language.Python) pythonParser Language.Python
|
||||
|
@ -15,8 +15,8 @@ import qualified Data.Language as Language
|
||||
import SpecHelpers
|
||||
|
||||
|
||||
spec :: Spec
|
||||
spec = parallel $ do
|
||||
spec :: TaskConfig -> Spec
|
||||
spec config = parallel $ do
|
||||
describe "Ruby" $ do
|
||||
it "evaluates require_relative" $ do
|
||||
(_, (heap, res)) <- evaluate ["main.rb", "foo.rb"]
|
||||
@ -104,4 +104,4 @@ spec = parallel $ do
|
||||
ns n = Just . Latest . Last . Just . Namespace n
|
||||
fixtures = "test/fixtures/ruby/analysis/"
|
||||
evaluate = evalRubyProject . map (fixtures <>)
|
||||
evalRubyProject = testEvaluating <=< evaluateProject (Proxy :: Proxy 'Language.Ruby) rubyParser Language.Ruby
|
||||
evalRubyProject = testEvaluating <=< evaluateProject' config (Proxy :: Proxy 'Language.Ruby) rubyParser Language.Ruby
|
||||
|
@ -11,8 +11,8 @@ import qualified Data.List.NonEmpty as NonEmpty
|
||||
import Data.Sum
|
||||
import SpecHelpers
|
||||
|
||||
spec :: Spec
|
||||
spec = parallel $ do
|
||||
spec :: TaskConfig -> Spec
|
||||
spec config = parallel $ do
|
||||
describe "TypeScript" $ do
|
||||
it "imports with aliased symbols" $ do
|
||||
(_, (_, res)) <- evaluate ["main.ts", "foo.ts", "a.ts", "foo/b.ts"]
|
||||
@ -49,4 +49,4 @@ spec = parallel $ do
|
||||
where
|
||||
fixtures = "test/fixtures/typescript/analysis/"
|
||||
evaluate = evalTypeScriptProject . map (fixtures <>)
|
||||
evalTypeScriptProject = testEvaluating <=< evaluateProject (Proxy :: Proxy 'Language.TypeScript) typescriptParser Language.TypeScript
|
||||
evalTypeScriptProject = testEvaluating <=< evaluateProject' config (Proxy :: Proxy 'Language.TypeScript) typescriptParser Language.TypeScript
|
||||
|
@ -11,8 +11,8 @@ import SpecHelpers
|
||||
languages :: [FilePath]
|
||||
languages = ["go", "javascript", "json", "python", "ruby", "typescript"]
|
||||
|
||||
spec :: Spec
|
||||
spec = parallel $ do
|
||||
spec :: TaskConfig -> Spec
|
||||
spec config = parallel $ do
|
||||
for_ languages $ \language -> do
|
||||
let dir = "test/fixtures" </> language </> "corpus"
|
||||
it (language <> " corpus exists") $ examples dir `shouldNotReturn` []
|
||||
@ -23,8 +23,8 @@ spec = parallel $ do
|
||||
runTestsIn directory pending = do
|
||||
examples <- runIO $ examples directory
|
||||
traverse_ (runTest pending) examples
|
||||
runTest pending ParseExample{..} = it ("parses " <> file) $ maybe (testParse file parseOutput) pendingWith (lookup parseOutput pending)
|
||||
runTest pending DiffExample{..} = it ("diffs " <> diffOutput) $ maybe (testDiff (both fileA fileB) diffOutput) pendingWith (lookup diffOutput pending)
|
||||
runTest pending ParseExample{..} = it ("parses " <> file) $ maybe (testParse config file parseOutput) pendingWith (lookup parseOutput pending)
|
||||
runTest pending DiffExample{..} = it ("diffs " <> diffOutput) $ maybe (testDiff config (both fileA fileB) diffOutput) pendingWith (lookup diffOutput pending)
|
||||
|
||||
data Example = DiffExample { fileA :: FilePath, fileB :: FilePath, diffOutput :: FilePath }
|
||||
| ParseExample { file :: FilePath, parseOutput :: FilePath }
|
||||
@ -81,14 +81,14 @@ examples directory = do
|
||||
normalizeName :: FilePath -> FilePath
|
||||
normalizeName path = dropExtension $ dropExtension path
|
||||
|
||||
testParse :: FilePath -> FilePath -> Expectation
|
||||
testParse path expectedOutput = do
|
||||
actual <- verbatim <$> parseFilePath path
|
||||
testParse :: TaskConfig -> FilePath -> FilePath -> Expectation
|
||||
testParse config path expectedOutput = do
|
||||
actual <- verbatim <$> parseFilePath config path
|
||||
expected <- verbatim <$> B.readFile expectedOutput
|
||||
actual `shouldBe` expected
|
||||
|
||||
testDiff :: Both FilePath -> FilePath -> Expectation
|
||||
testDiff paths expectedOutput = do
|
||||
actual <- verbatim <$> diffFilePaths paths
|
||||
testDiff :: TaskConfig -> Both FilePath -> FilePath -> Expectation
|
||||
testDiff config paths expectedOutput = do
|
||||
actual <- verbatim <$> diffFilePaths config paths
|
||||
expected <- verbatim <$> B.readFile expectedOutput
|
||||
actual `shouldBe` expected
|
||||
|
59
test/Spec.hs
59
test/Spec.hs
@ -24,34 +24,39 @@ import qualified Semantic.Spec
|
||||
import qualified Semantic.CLI.Spec
|
||||
import qualified Semantic.IO.Spec
|
||||
import qualified Semantic.Stat.Spec
|
||||
import Semantic.Config (defaultOptions)
|
||||
import Semantic.Task (withOptions)
|
||||
import Semantic.Util (TaskConfig(..))
|
||||
import qualified Proto3.Roundtrip
|
||||
import Test.Hspec
|
||||
|
||||
main :: IO ()
|
||||
main = hspec $ do
|
||||
describe "Semantic.Stat" Semantic.Stat.Spec.spec
|
||||
parallel $ do
|
||||
describe "Analysis.Go" Analysis.Go.Spec.spec
|
||||
describe "Analysis.PHP" Analysis.PHP.Spec.spec
|
||||
describe "Analysis.Python" Analysis.Python.Spec.spec
|
||||
describe "Analysis.Ruby" Analysis.Ruby.Spec.spec
|
||||
describe "Analysis.TypeScript" Analysis.TypeScript.Spec.spec
|
||||
describe "Assigning.Assignment" Assigning.Assignment.Spec.spec
|
||||
describe "Control.Abstract.Evaluator" Control.Abstract.Evaluator.Spec.spec
|
||||
describe "Data.Diff" Data.Diff.Spec.spec
|
||||
describe "Data.Abstract.Path" Data.Abstract.Path.Spec.spec
|
||||
describe "Data.Functor.Classes.Generic" Data.Functor.Classes.Generic.Spec.spec
|
||||
describe "Data.Scientific" Data.Scientific.Spec.spec
|
||||
describe "Data.Source" Data.Source.Spec.spec
|
||||
describe "Data.Term" Data.Term.Spec.spec
|
||||
describe "Diffing.Algorithm.RWS" Diffing.Algorithm.RWS.Spec.spec
|
||||
describe "Diffing.Algorithm.SES" Diffing.Algorithm.SES.Spec.spec
|
||||
describe "Diffing.Interpreter" Diffing.Interpreter.Spec.spec
|
||||
describe "Matching" Matching.Go.Spec.spec
|
||||
describe "Numeric" Numeric.Spec.spec
|
||||
describe "Rendering.TOC" Rendering.TOC.Spec.spec
|
||||
describe "Semantic" Semantic.Spec.spec
|
||||
describe "Semantic.CLI" Semantic.CLI.Spec.spec
|
||||
describe "Semantic.IO" Semantic.IO.Spec.spec
|
||||
describe "Integration" Integration.Spec.spec
|
||||
describe "Protobuf roundtripping" Proto3.Roundtrip.spec
|
||||
main = do
|
||||
withOptions defaultOptions $ \ config logger statter -> hspec $ do
|
||||
let args = TaskConfig config logger statter
|
||||
describe "Semantic.Stat" Semantic.Stat.Spec.spec
|
||||
parallel $ do
|
||||
describe "Analysis.Go" (Analysis.Go.Spec.spec args)
|
||||
describe "Analysis.PHP" (Analysis.PHP.Spec.spec args)
|
||||
describe "Analysis.Python" (Analysis.Python.Spec.spec args)
|
||||
describe "Analysis.Ruby" (Analysis.Ruby.Spec.spec args)
|
||||
describe "Analysis.TypeScript" (Analysis.TypeScript.Spec.spec args)
|
||||
describe "Assigning.Assignment" Assigning.Assignment.Spec.spec
|
||||
describe "Control.Abstract.Evaluator" Control.Abstract.Evaluator.Spec.spec
|
||||
describe "Data.Diff" Data.Diff.Spec.spec
|
||||
describe "Data.Abstract.Path" Data.Abstract.Path.Spec.spec
|
||||
describe "Data.Functor.Classes.Generic" Data.Functor.Classes.Generic.Spec.spec
|
||||
describe "Data.Scientific" Data.Scientific.Spec.spec
|
||||
describe "Data.Source" Data.Source.Spec.spec
|
||||
describe "Data.Term" Data.Term.Spec.spec
|
||||
describe "Diffing.Algorithm.RWS" Diffing.Algorithm.RWS.Spec.spec
|
||||
describe "Diffing.Algorithm.SES" Diffing.Algorithm.SES.Spec.spec
|
||||
describe "Diffing.Interpreter" Diffing.Interpreter.Spec.spec
|
||||
describe "Matching" Matching.Go.Spec.spec
|
||||
describe "Numeric" Numeric.Spec.spec
|
||||
describe "Rendering.TOC" Rendering.TOC.Spec.spec
|
||||
describe "Semantic" Semantic.Spec.spec
|
||||
describe "Semantic.CLI" Semantic.CLI.Spec.spec
|
||||
describe "Semantic.IO" Semantic.IO.Spec.spec
|
||||
describe "Integration" (Integration.Spec.spec args)
|
||||
describe "Protobuf roundtripping" Proto3.Roundtrip.spec
|
||||
|
@ -11,6 +11,9 @@ module SpecHelpers
|
||||
, TermEvaluator(..)
|
||||
, Verbatim(..)
|
||||
, toList
|
||||
, Config
|
||||
, LogQueue
|
||||
, StatQueue
|
||||
) where
|
||||
|
||||
import Control.Abstract
|
||||
@ -65,16 +68,20 @@ import Test.LeanCheck as X
|
||||
|
||||
import qualified Data.ByteString as B
|
||||
import qualified Semantic.IO as IO
|
||||
import Semantic.Config (Config)
|
||||
import Semantic.Telemetry (LogQueue, StatQueue)
|
||||
import System.Exit (die)
|
||||
import Control.Exception (displayException)
|
||||
|
||||
runBuilder = toStrict . toLazyByteString
|
||||
|
||||
-- | Returns an s-expression formatted diff for the specified FilePath pair.
|
||||
diffFilePaths :: Both FilePath -> IO ByteString
|
||||
diffFilePaths paths = readFilePair paths >>= fmap runBuilder . runTask . runDiff SExpressionDiffRenderer . pure
|
||||
diffFilePaths :: TaskConfig -> Both FilePath -> IO ByteString
|
||||
diffFilePaths (TaskConfig config logger statter) paths = readFilePair paths >>= runTaskWithConfig config logger statter . runDiff SExpressionDiffRenderer . pure >>= either (die . displayException) (pure . runBuilder)
|
||||
|
||||
-- | Returns an s-expression parse tree for the specified FilePath.
|
||||
parseFilePath :: FilePath -> IO ByteString
|
||||
parseFilePath path = (fromJust <$> IO.readFile (file path)) >>= fmap runBuilder . runTask . runParse SExpressionTermRenderer . pure
|
||||
parseFilePath :: TaskConfig -> FilePath -> IO ByteString
|
||||
parseFilePath (TaskConfig config logger statter) path = (fromJust <$> IO.readFile (file path)) >>= runTaskWithConfig config logger statter . runParse SExpressionTermRenderer . pure >>= either (die . displayException) (pure . runBuilder)
|
||||
|
||||
-- | Read two files to a BlobPair.
|
||||
readFilePair :: Both FilePath -> IO BlobPair
|
||||
|
Loading…
Reference in New Issue
Block a user