mirror of
https://github.com/github/semantic.git
synced 2024-12-24 15:35:14 +03:00
Remove unnecessary use of parallel
.
This commit is contained in:
parent
6306f07cc1
commit
43e3fb4533
@ -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"]
|
||||
|
@ -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"]
|
||||
|
@ -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"]
|
||||
|
@ -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"]
|
||||
|
@ -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"]
|
||||
|
@ -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))
|
||||
|
@ -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 () ())
|
||||
|
@ -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" $
|
||||
|
@ -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
|
||||
|
@ -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 ())
|
||||
|
@ -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" $
|
||||
|
@ -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"))
|
||||
|
@ -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
|
||||
|
@ -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` []
|
||||
|
@ -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
|
||||
|
@ -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 ]
|
||||
|
@ -66,7 +66,6 @@ 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
|
||||
|
@ -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"
|
||||
|
Loading…
Reference in New Issue
Block a user