1
1
mirror of https://github.com/github/semantic.git synced 2024-12-23 23:11:50 +03:00

Remove unnecessary use of parallel.

This commit is contained in:
Patrick Thomson 2019-06-19 17:22:09 -04:00
parent 6306f07cc1
commit 43e3fb4533
18 changed files with 48 additions and 51 deletions

View File

@ -8,7 +8,7 @@ import SpecHelpers
spec :: (?session :: TaskSession) => Spec
spec = parallel $ do
spec = do
describe "Go" $ do
it "imports and wildcard imports" $ do
(scopeGraph, (heap, res)) <- evaluate ["main.go", "foo/foo.go", "bar/bar.go", "bar/rab.go"]

View File

@ -9,7 +9,7 @@ import SpecHelpers
spec :: (?session :: TaskSession) => Spec
spec = parallel $ do
spec = do
describe "PHP" $ do
xit "evaluates include and require" $ do
(scopeGraph, (heap, res)) <- evaluate ["main.php", "foo.php", "bar.php"]

View File

@ -10,7 +10,7 @@ import SpecHelpers
spec :: (?session :: TaskSession) => Spec
spec = parallel $ do
spec = do
describe "Python" $ do
it "imports" $ do
(scopeGraph, (heap, res)) <- evaluate ["main.py", "a.py", "b/__init__.py", "b/c.py"]

View File

@ -15,7 +15,7 @@ import SpecHelpers
spec :: (?session :: TaskSession) => Spec
spec = parallel $ do
spec = do
describe "Ruby" $ do
it "evaluates require_relative" $ do
(scopeGraph, (heap, res)) <- evaluate ["main.rb", "foo.rb"]

View File

@ -23,7 +23,7 @@ import qualified Language.TypeScript.Assignment as TypeScript
import SpecHelpers
spec :: (?session :: TaskSession) => Spec
spec = parallel $ do
spec = do
describe "TypeScript" $ do
it "qualified export from" $ do
(scopeGraph, (heap, res)) <- evaluate ["main6.ts", "baz.ts", "foo.ts"]

View File

@ -21,7 +21,7 @@ import SpecHelpers hiding (reassociate)
import System.IO.Unsafe (unsafePerformIO)
spec :: Spec
spec = parallel $ do
spec = do
it "constructs integers" $ do
(_, (_, (_, expected))) <- evaluate (integer 123)
expected `shouldBe` Right (Value.Integer (Number.Integer 123))

View File

@ -7,6 +7,6 @@ import Test.Hspec
import Test.Hspec.LeanCheck
spec :: Spec
spec = parallel $ do
spec = do
prop "equality is reflexive" $
\ diff -> diff `shouldBe` (diff :: Diff ListableSyntax () ())

View File

@ -7,7 +7,7 @@ import Test.Hspec
import Test.Hspec.LeanCheck
spec :: Spec
spec = parallel $ do
spec = do
describe "Eq1" $ do
describe "genericLiftEq" $ do
prop "equivalent to derived (==) for product types" $

View File

@ -70,7 +70,7 @@ testTree = Tasty.testGroup "Data.Source"
]
spec :: Spec
spec = parallel $ do
spec = do
describe "newlineIndices" $ do
it "finds \\n" $
let source = "a\nb" in

View File

@ -8,7 +8,7 @@ import Test.Hspec.Expectations
import Test.Hspec.LeanCheck
spec :: Spec
spec = parallel $ do
spec = do
describe "Term" $ do
prop "equality is reflexive" $
\ a -> a `shouldBe` (a :: Term ListableSyntax ())

View File

@ -16,7 +16,7 @@ import Test.Hspec.LeanCheck
import SpecHelpers
spec :: Spec
spec = parallel $ do
spec = do
let positively = succ . abs
describe "pqGramDecorator" $ do
prop "produces grams with stems of the specified length" $

View File

@ -21,7 +21,7 @@ import Test.LeanCheck.Core
import SpecHelpers ()
spec :: Spec
spec = parallel $ do
spec = do
describe "diffTerms" $ do
it "returns a replacement when comparing two unicode equivalent terms" $
let termA = termIn emptyAnnotation (inject (Syntax.Identifier "t\776"))

View File

@ -12,7 +12,7 @@ import SpecHelpers
import TreeSitter.JSON (tree_sitter_json, Grammar)
spec :: Spec
spec = parallel $ do
spec = do
describe "parseToAST" $ do
let source = toJSONSource [1 :: Int .. 10000]
let largeBlob = sourceBlob "large.json" JSON source

View File

@ -28,7 +28,7 @@ import SpecHelpers
spec :: Spec
spec = parallel $ do
spec = do
describe "tableOfContentsBy" $ do
prop "drops all nodes with the constant Nothing function" $
\ diff -> tableOfContentsBy (const Nothing :: a -> Maybe ()) (diff :: Diff ListableSyntax () ()) `shouldBe` []

View File

@ -16,7 +16,7 @@ import qualified Semantic.Git as Git
import Shelly (shelly, silently, cd, run_)
spec :: Spec
spec = parallel $ do
spec = do
describe "readBlobsFromGitRepo" $ do
hasGit <- runIO $ isJust <$> findExecutable "git"
when hasGit . it "should read from a git directory" $ do
@ -50,9 +50,7 @@ spec = parallel $ do
let a = sourceBlob "method.rb" Ruby "def foo; end"
let b = sourceBlob "method.rb" Ruby "def bar(x); end"
it "returns blobs for valid JSON encoded diff input" $ do
putStrLn "step 1"
blobs <- blobsFromFilePath "test/fixtures/cli/diff.json"
putStrLn "done"
blobs `shouldBe` [Diffing a b]
it "returns blobs when there's no before" $ do

View File

@ -12,7 +12,7 @@ setBlobLanguage :: Language -> Blob -> Blob
setBlobLanguage lang b = b { blobFile = (blobFile b) { fileLanguage = lang }}
spec :: Spec
spec = parallel $ do
spec = do
describe "parseBlob" $ do
it "returns error if given an unknown language (json)" $ do
output <- fmap runBuilder . runTaskOrDie $ parseTermBuilder TermJSONTree [ setBlobLanguage Unknown methodsBlob ]

View File

@ -66,38 +66,37 @@ allTests = do
legacySpecs :: (?session :: TaskSession) => Spec
legacySpecs = 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.Graph" Data.Graph.Spec.spec
describe "Data.Abstract.Path" Data.Abstract.Path.Spec.spec
describe "Data.Abstract.Name" Data.Abstract.Name.Spec.spec
describe "Data.Functor.Classes.Generic" Data.Functor.Classes.Generic.Spec.spec
describe "Data.Range" Data.Range.Spec.spec
describe "Data.Scientific" Data.Scientific.Spec.spec
describe "Data.Semigroup.App" Data.Semigroup.App.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 "Graphing.Calls" Graphing.Calls.Spec.spec
describe "Numeric" Numeric.Spec.spec
describe "Rendering.TOC" Rendering.TOC.Spec.spec
describe "Reprinting.Spec" Reprinting.Spec.spec
describe "Rewriting.Go" Rewriting.Go.Spec.spec
describe "Rewriting.JSON" Rewriting.JSON.Spec.spec
describe "Rewriting.Python" Rewriting.Python.Spec.spec
describe "Tags.Spec" Tags.Spec.spec
describe "Semantic" Semantic.Spec.spec
describe "Semantic.IO" Semantic.IO.Spec.spec
describe "Parsing" Parsing.Spec.spec
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.Graph" Data.Graph.Spec.spec
describe "Data.Abstract.Path" Data.Abstract.Path.Spec.spec
describe "Data.Abstract.Name" Data.Abstract.Name.Spec.spec
describe "Data.Functor.Classes.Generic" Data.Functor.Classes.Generic.Spec.spec
describe "Data.Range" Data.Range.Spec.spec
describe "Data.Scientific" Data.Scientific.Spec.spec
describe "Data.Semigroup.App" Data.Semigroup.App.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 "Graphing.Calls" Graphing.Calls.Spec.spec
describe "Numeric" Numeric.Spec.spec
describe "Rendering.TOC" Rendering.TOC.Spec.spec
describe "Reprinting.Spec" Reprinting.Spec.spec
describe "Rewriting.Go" Rewriting.Go.Spec.spec
describe "Rewriting.JSON" Rewriting.JSON.Spec.spec
describe "Rewriting.Python" Rewriting.Python.Spec.spec
describe "Tags.Spec" Tags.Spec.spec
describe "Semantic" Semantic.Spec.spec
describe "Semantic.IO" Semantic.IO.Spec.spec
describe "Parsing" Parsing.Spec.spec
main :: IO ()

View File

@ -6,7 +6,7 @@ import Tags.Tagging
spec :: Spec
spec = parallel $ do
spec = do
describe "go" $ do
it "produces tags for functions with docs" $ do
(blob, tree) <- parseTestFile goParser "test/fixtures/go/tags/simple_functions.go"