Skip to content
This repository was archived by the owner on Apr 1, 2025. It is now read-only.
Merged
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
7 changes: 4 additions & 3 deletions test/Analysis/Go/Spec.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,4 @@
{-# LANGUAGE ImplicitParams #-}
{-# OPTIONS_GHC -O0 #-}
module Analysis.Go.Spec (spec) where

Expand All @@ -6,8 +7,8 @@ import qualified Data.Language as Language
import SpecHelpers


spec :: TaskSession -> Spec
spec session = parallel $ do
spec :: (?session :: TaskSession) => Spec
Copy link
Contributor

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

You could define this as a constraint synonym somewhere and lose the LANGUAGE pragma as well as simplifying the syntax, rather like HasCallStack. (You’d also need a currentSession binding which uses it.)

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"]
Expand All @@ -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
7 changes: 4 additions & 3 deletions test/Analysis/PHP/Spec.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,4 @@
{-# LANGUAGE ImplicitParams #-}
{-# OPTIONS_GHC -O0 #-}
module Analysis.PHP.Spec (spec) where

Expand All @@ -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"]
Expand Down Expand Up @@ -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
7 changes: 4 additions & 3 deletions test/Analysis/Python/Spec.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,4 @@
{-# LANGUAGE ImplicitParams #-}
{-# OPTIONS_GHC -O0 #-}
module Analysis.Python.Spec (spec) where

Expand All @@ -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"]
Expand Down Expand Up @@ -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
8 changes: 4 additions & 4 deletions test/Analysis/Ruby/Spec.hs
Original file line number Diff line number Diff line change
@@ -1,5 +1,5 @@
{-# OPTIONS_GHC -O0 #-}
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE ImplicitParams, TupleSections #-}
module Analysis.Ruby.Spec (spec) where

import Control.Abstract (Declaration (..), ScopeError (..))
Expand All @@ -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"]
Expand Down Expand Up @@ -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
7 changes: 4 additions & 3 deletions test/Analysis/TypeScript/Spec.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,4 @@
{-# LANGUAGE ImplicitParams #-}
{-# OPTIONS_GHC -O0 #-}

module Analysis.TypeScript.Spec (spec) where
Expand All @@ -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"]
Expand Down Expand Up @@ -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))
4 changes: 2 additions & 2 deletions test/Integration/Spec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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
Expand Down
35 changes: 18 additions & 17 deletions test/Spec.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,5 @@
{-# LANGUAGE ImplicitParams #-}

module Main where

import qualified Analysis.Go.Spec
Expand Down Expand Up @@ -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
Expand All @@ -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
Expand Down Expand Up @@ -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