mirror of
https://github.com/github/semantic.git
synced 2024-11-24 08:54:07 +03:00
Merge pull request #129 from github/cleaner-implicit-params
Clean up specs with some implicit parameters.
This commit is contained in:
commit
e4fdb7f492
@ -1,3 +1,4 @@
|
||||
{-# LANGUAGE ImplicitParams #-}
|
||||
{-# OPTIONS_GHC -O0 #-}
|
||||
module Analysis.Go.Spec (spec) where
|
||||
|
||||
@ -6,8 +7,8 @@ import qualified Data.Language as Language
|
||||
import SpecHelpers
|
||||
|
||||
|
||||
spec :: TaskSession -> Spec
|
||||
spec session = parallel $ do
|
||||
spec :: (?session :: TaskSession) => Spec
|
||||
spec = parallel $ 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"]
|
||||
@ -32,4 +33,4 @@ spec session = parallel $ do
|
||||
where
|
||||
fixtures = "test/fixtures/go/analysis/"
|
||||
evaluate = evalGoProject . map (fixtures <>)
|
||||
evalGoProject = testEvaluating <=< evaluateProject' session (Proxy :: Proxy 'Language.Go) goParser
|
||||
evalGoProject = testEvaluating <=< evaluateProject' ?session (Proxy :: Proxy 'Language.Go) goParser
|
||||
|
@ -1,3 +1,4 @@
|
||||
{-# LANGUAGE ImplicitParams #-}
|
||||
{-# OPTIONS_GHC -O0 #-}
|
||||
module Analysis.PHP.Spec (spec) where
|
||||
|
||||
@ -7,8 +8,8 @@ import qualified Data.Language as Language
|
||||
import SpecHelpers
|
||||
|
||||
|
||||
spec :: TaskSession -> Spec
|
||||
spec session = parallel $ do
|
||||
spec :: (?session :: TaskSession) => Spec
|
||||
spec = parallel $ do
|
||||
describe "PHP" $ do
|
||||
xit "evaluates include and require" $ do
|
||||
(scopeGraph, (heap, res)) <- evaluate ["main.php", "foo.php", "bar.php"]
|
||||
@ -44,4 +45,4 @@ spec session = parallel $ do
|
||||
where
|
||||
fixtures = "test/fixtures/php/analysis/"
|
||||
evaluate = evalPHPProject . map (fixtures <>)
|
||||
evalPHPProject = testEvaluating <=< evaluateProject' session (Proxy :: Proxy 'Language.PHP) phpParser
|
||||
evalPHPProject = testEvaluating <=< evaluateProject' ?session (Proxy :: Proxy 'Language.PHP) phpParser
|
||||
|
@ -1,3 +1,4 @@
|
||||
{-# LANGUAGE ImplicitParams #-}
|
||||
{-# OPTIONS_GHC -O0 #-}
|
||||
module Analysis.Python.Spec (spec) where
|
||||
|
||||
@ -8,8 +9,8 @@ import qualified Data.Language as Language
|
||||
import SpecHelpers
|
||||
|
||||
|
||||
spec :: TaskSession -> Spec
|
||||
spec session = parallel $ do
|
||||
spec :: (?session :: TaskSession) => Spec
|
||||
spec = parallel $ do
|
||||
describe "Python" $ do
|
||||
it "imports" $ do
|
||||
(scopeGraph, (heap, res)) <- evaluate ["main.py", "a.py", "b/__init__.py", "b/c.py"]
|
||||
@ -71,4 +72,4 @@ spec session = parallel $ do
|
||||
where
|
||||
fixtures = "test/fixtures/python/analysis/"
|
||||
evaluate = evalPythonProject . map (fixtures <>)
|
||||
evalPythonProject = testEvaluating <=< evaluateProject' session (Proxy :: Proxy 'Language.Python) pythonParser
|
||||
evalPythonProject = testEvaluating <=< evaluateProject' ?session (Proxy :: Proxy 'Language.Python) pythonParser
|
||||
|
@ -1,5 +1,5 @@
|
||||
{-# OPTIONS_GHC -O0 #-}
|
||||
{-# LANGUAGE TupleSections #-}
|
||||
{-# LANGUAGE ImplicitParams, TupleSections #-}
|
||||
module Analysis.Ruby.Spec (spec) where
|
||||
|
||||
import Control.Abstract (Declaration (..), ScopeError (..))
|
||||
@ -14,8 +14,8 @@ import Data.Sum
|
||||
import SpecHelpers
|
||||
|
||||
|
||||
spec :: TaskSession -> Spec
|
||||
spec session = parallel $ do
|
||||
spec :: (?session :: TaskSession) => Spec
|
||||
spec = parallel $ do
|
||||
describe "Ruby" $ do
|
||||
it "evaluates require_relative" $ do
|
||||
(scopeGraph, (heap, res)) <- evaluate ["main.rb", "foo.rb"]
|
||||
@ -101,4 +101,4 @@ spec session = parallel $ do
|
||||
where
|
||||
fixtures = "test/fixtures/ruby/analysis/"
|
||||
evaluate = evalRubyProject . map (fixtures <>)
|
||||
evalRubyProject = testEvaluating <=< evaluateProject' session (Proxy :: Proxy 'Language.Ruby) rubyParser
|
||||
evalRubyProject = testEvaluating <=< evaluateProject' ?session (Proxy :: Proxy 'Language.Ruby) rubyParser
|
||||
|
@ -1,3 +1,4 @@
|
||||
{-# LANGUAGE ImplicitParams #-}
|
||||
{-# OPTIONS_GHC -O0 #-}
|
||||
|
||||
module Analysis.TypeScript.Spec (spec) where
|
||||
@ -21,8 +22,8 @@ import Data.Text (pack)
|
||||
import qualified Language.TypeScript.Assignment as TypeScript
|
||||
import SpecHelpers
|
||||
|
||||
spec :: TaskSession -> Spec
|
||||
spec session = parallel $ do
|
||||
spec :: (?session :: TaskSession) => Spec
|
||||
spec = parallel $ do
|
||||
describe "TypeScript" $ do
|
||||
it "qualified export from" $ do
|
||||
(scopeGraph, (heap, res)) <- evaluate ["main6.ts", "baz.ts", "foo.ts"]
|
||||
@ -181,7 +182,7 @@ spec session = parallel $ do
|
||||
where
|
||||
fixtures = "test/fixtures/typescript/analysis/"
|
||||
evaluate = evalTypeScriptProject . map (fixtures <>)
|
||||
evalTypeScriptProject = testEvaluating <=< (evaluateProject' session (Proxy :: Proxy 'Language.TypeScript) typescriptParser)
|
||||
evalTypeScriptProject = testEvaluating <=< (evaluateProject' ?session (Proxy :: Proxy 'Language.TypeScript) typescriptParser)
|
||||
|
||||
type TypeScriptTerm = Quieterm (Sum TypeScript.Syntax) Location
|
||||
type TypeScriptEvalError = BaseError (EvalError TypeScriptTerm Precise (Concrete.Value TypeScriptTerm Precise))
|
||||
|
@ -17,8 +17,8 @@ import Test.Tasty.Golden
|
||||
languages :: [FilePath]
|
||||
languages = ["go", "javascript", "json", "python", "ruby", "typescript", "tsx"]
|
||||
|
||||
spec :: TaskSession -> TestTree
|
||||
spec config = let ?session = config in testGroup "Integration (golden tests)" $ fmap testsForLanguage languages
|
||||
spec :: (?session :: TaskSession) => TestTree
|
||||
spec = testGroup "Integration (golden tests)" $ fmap testsForLanguage languages
|
||||
|
||||
testsForLanguage :: (?session :: TaskSession) => FilePath -> TestTree
|
||||
testsForLanguage language = do
|
||||
|
35
test/Spec.hs
35
test/Spec.hs
@ -1,3 +1,5 @@
|
||||
{-# LANGUAGE ImplicitParams #-}
|
||||
|
||||
module Main where
|
||||
|
||||
import qualified Analysis.Go.Spec
|
||||
@ -40,19 +42,18 @@ import Test.Hspec
|
||||
import Test.Tasty as Tasty
|
||||
import Test.Tasty.Hspec as Tasty
|
||||
|
||||
tests :: TaskSession -> [TestTree]
|
||||
tests session =
|
||||
[ Integration.Spec.spec session
|
||||
tests :: (?session :: TaskSession) => [TestTree]
|
||||
tests =
|
||||
[ Integration.Spec.spec
|
||||
, Semantic.CLI.Spec.spec
|
||||
]
|
||||
|
||||
-- We can't bring this out of the IO monad until we divest
|
||||
-- from hspec, since testSpec operates in IO.
|
||||
allTests :: TaskSession -> IO TestTree
|
||||
allTests session = do
|
||||
let nativeSpecs = tests session
|
||||
asTastySpecs <- Tasty.testSpecs $ legacySpecs session
|
||||
let allSpecs = nativeSpecs <> asTastySpecs
|
||||
allTests :: (?session :: TaskSession) => IO TestTree
|
||||
allTests = do
|
||||
asTastySpecs <- Tasty.testSpecs legacySpecs
|
||||
let allSpecs = tests <> asTastySpecs
|
||||
pure . Tasty.localOption Tasty.Success $ testGroup "semantic" allSpecs
|
||||
|
||||
-- If you're writing new test modules, please don't add to this
|
||||
@ -61,15 +62,15 @@ allTests session = do
|
||||
-- documentation: "hspec and tasty serve similar purposes; consider
|
||||
-- using one or the other.") Instead, create a new TestTree value
|
||||
-- in your spec module and add it to the above 'tests' list.
|
||||
legacySpecs :: TaskSession -> Spec
|
||||
legacySpecs args = do
|
||||
legacySpecs :: (?session :: TaskSession) => Spec
|
||||
legacySpecs = do
|
||||
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 "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
|
||||
@ -101,6 +102,6 @@ legacySpecs args = do
|
||||
main :: IO ()
|
||||
main = do
|
||||
withOptions defaultOptions { optionsLogLevel = Nothing } $ \ config logger statter ->
|
||||
let session = TaskSession config "-" False logger statter
|
||||
in allTests session >>= defaultMain
|
||||
let ?session = TaskSession config "-" False logger statter
|
||||
in allTests >>= defaultMain
|
||||
|
||||
|
Loading…
Reference in New Issue
Block a user