Skip to content
This repository was archived by the owner on Apr 1, 2025. It is now read-only.

Commit e4fdb7f

Browse files
author
Patrick Thomson
authored
Merge pull request #129 from github/cleaner-implicit-params
Clean up specs with some implicit parameters.
2 parents c6607e4 + 6edabbb commit e4fdb7f

File tree

7 files changed

+40
-35
lines changed

7 files changed

+40
-35
lines changed

test/Analysis/Go/Spec.hs

Lines changed: 4 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,4 @@
1+
{-# LANGUAGE ImplicitParams #-}
12
{-# OPTIONS_GHC -O0 #-}
23
module Analysis.Go.Spec (spec) where
34

@@ -6,8 +7,8 @@ import qualified Data.Language as Language
67
import SpecHelpers
78

89

9-
spec :: TaskSession -> Spec
10-
spec session = parallel $ do
10+
spec :: (?session :: TaskSession) => Spec
11+
spec = parallel $ do
1112
describe "Go" $ do
1213
it "imports and wildcard imports" $ do
1314
(scopeGraph, (heap, res)) <- evaluate ["main.go", "foo/foo.go", "bar/bar.go", "bar/rab.go"]
@@ -32,4 +33,4 @@ spec session = parallel $ do
3233
where
3334
fixtures = "test/fixtures/go/analysis/"
3435
evaluate = evalGoProject . map (fixtures <>)
35-
evalGoProject = testEvaluating <=< evaluateProject' session (Proxy :: Proxy 'Language.Go) goParser
36+
evalGoProject = testEvaluating <=< evaluateProject' ?session (Proxy :: Proxy 'Language.Go) goParser

test/Analysis/PHP/Spec.hs

Lines changed: 4 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,4 @@
1+
{-# LANGUAGE ImplicitParams #-}
12
{-# OPTIONS_GHC -O0 #-}
23
module Analysis.PHP.Spec (spec) where
34

@@ -7,8 +8,8 @@ import qualified Data.Language as Language
78
import SpecHelpers
89

910

10-
spec :: TaskSession -> Spec
11-
spec session = parallel $ do
11+
spec :: (?session :: TaskSession) => Spec
12+
spec = parallel $ do
1213
describe "PHP" $ do
1314
xit "evaluates include and require" $ do
1415
(scopeGraph, (heap, res)) <- evaluate ["main.php", "foo.php", "bar.php"]
@@ -44,4 +45,4 @@ spec session = parallel $ do
4445
where
4546
fixtures = "test/fixtures/php/analysis/"
4647
evaluate = evalPHPProject . map (fixtures <>)
47-
evalPHPProject = testEvaluating <=< evaluateProject' session (Proxy :: Proxy 'Language.PHP) phpParser
48+
evalPHPProject = testEvaluating <=< evaluateProject' ?session (Proxy :: Proxy 'Language.PHP) phpParser

test/Analysis/Python/Spec.hs

Lines changed: 4 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,4 @@
1+
{-# LANGUAGE ImplicitParams #-}
12
{-# OPTIONS_GHC -O0 #-}
23
module Analysis.Python.Spec (spec) where
34

@@ -8,8 +9,8 @@ import qualified Data.Language as Language
89
import SpecHelpers
910

1011

11-
spec :: TaskSession -> Spec
12-
spec session = parallel $ do
12+
spec :: (?session :: TaskSession) => Spec
13+
spec = parallel $ do
1314
describe "Python" $ do
1415
it "imports" $ do
1516
(scopeGraph, (heap, res)) <- evaluate ["main.py", "a.py", "b/__init__.py", "b/c.py"]
@@ -71,4 +72,4 @@ spec session = parallel $ do
7172
where
7273
fixtures = "test/fixtures/python/analysis/"
7374
evaluate = evalPythonProject . map (fixtures <>)
74-
evalPythonProject = testEvaluating <=< evaluateProject' session (Proxy :: Proxy 'Language.Python) pythonParser
75+
evalPythonProject = testEvaluating <=< evaluateProject' ?session (Proxy :: Proxy 'Language.Python) pythonParser

test/Analysis/Ruby/Spec.hs

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,5 @@
11
{-# OPTIONS_GHC -O0 #-}
2-
{-# LANGUAGE TupleSections #-}
2+
{-# LANGUAGE ImplicitParams, TupleSections #-}
33
module Analysis.Ruby.Spec (spec) where
44

55
import Control.Abstract (Declaration (..), ScopeError (..))
@@ -14,8 +14,8 @@ import Data.Sum
1414
import SpecHelpers
1515

1616

17-
spec :: TaskSession -> Spec
18-
spec session = parallel $ do
17+
spec :: (?session :: TaskSession) => Spec
18+
spec = parallel $ do
1919
describe "Ruby" $ do
2020
it "evaluates require_relative" $ do
2121
(scopeGraph, (heap, res)) <- evaluate ["main.rb", "foo.rb"]
@@ -101,4 +101,4 @@ spec session = parallel $ do
101101
where
102102
fixtures = "test/fixtures/ruby/analysis/"
103103
evaluate = evalRubyProject . map (fixtures <>)
104-
evalRubyProject = testEvaluating <=< evaluateProject' session (Proxy :: Proxy 'Language.Ruby) rubyParser
104+
evalRubyProject = testEvaluating <=< evaluateProject' ?session (Proxy :: Proxy 'Language.Ruby) rubyParser

test/Analysis/TypeScript/Spec.hs

Lines changed: 4 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,4 @@
1+
{-# LANGUAGE ImplicitParams #-}
12
{-# OPTIONS_GHC -O0 #-}
23

34
module Analysis.TypeScript.Spec (spec) where
@@ -21,8 +22,8 @@ import Data.Text (pack)
2122
import qualified Language.TypeScript.Assignment as TypeScript
2223
import SpecHelpers
2324

24-
spec :: TaskSession -> Spec
25-
spec session = parallel $ do
25+
spec :: (?session :: TaskSession) => Spec
26+
spec = parallel $ do
2627
describe "TypeScript" $ do
2728
it "qualified export from" $ do
2829
(scopeGraph, (heap, res)) <- evaluate ["main6.ts", "baz.ts", "foo.ts"]
@@ -181,7 +182,7 @@ spec session = parallel $ do
181182
where
182183
fixtures = "test/fixtures/typescript/analysis/"
183184
evaluate = evalTypeScriptProject . map (fixtures <>)
184-
evalTypeScriptProject = testEvaluating <=< (evaluateProject' session (Proxy :: Proxy 'Language.TypeScript) typescriptParser)
185+
evalTypeScriptProject = testEvaluating <=< (evaluateProject' ?session (Proxy :: Proxy 'Language.TypeScript) typescriptParser)
185186

186187
type TypeScriptTerm = Quieterm (Sum TypeScript.Syntax) Location
187188
type TypeScriptEvalError = BaseError (EvalError TypeScriptTerm Precise (Concrete.Value TypeScriptTerm Precise))

test/Integration/Spec.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -17,8 +17,8 @@ import Test.Tasty.Golden
1717
languages :: [FilePath]
1818
languages = ["go", "javascript", "json", "python", "ruby", "typescript", "tsx"]
1919

20-
spec :: TaskSession -> TestTree
21-
spec config = let ?session = config in testGroup "Integration (golden tests)" $ fmap testsForLanguage languages
20+
spec :: (?session :: TaskSession) => TestTree
21+
spec = testGroup "Integration (golden tests)" $ fmap testsForLanguage languages
2222

2323
testsForLanguage :: (?session :: TaskSession) => FilePath -> TestTree
2424
testsForLanguage language = do

test/Spec.hs

Lines changed: 18 additions & 17 deletions
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,5 @@
1+
{-# LANGUAGE ImplicitParams #-}
2+
13
module Main where
24

35
import qualified Analysis.Go.Spec
@@ -40,19 +42,18 @@ import Test.Hspec
4042
import Test.Tasty as Tasty
4143
import Test.Tasty.Hspec as Tasty
4244

43-
tests :: TaskSession -> [TestTree]
44-
tests session =
45-
[ Integration.Spec.spec session
45+
tests :: (?session :: TaskSession) => [TestTree]
46+
tests =
47+
[ Integration.Spec.spec
4648
, Semantic.CLI.Spec.spec
4749
]
4850

4951
-- We can't bring this out of the IO monad until we divest
5052
-- from hspec, since testSpec operates in IO.
51-
allTests :: TaskSession -> IO TestTree
52-
allTests session = do
53-
let nativeSpecs = tests session
54-
asTastySpecs <- Tasty.testSpecs $ legacySpecs session
55-
let allSpecs = nativeSpecs <> asTastySpecs
53+
allTests :: (?session :: TaskSession) => IO TestTree
54+
allTests = do
55+
asTastySpecs <- Tasty.testSpecs legacySpecs
56+
let allSpecs = tests <> asTastySpecs
5657
pure . Tasty.localOption Tasty.Success $ testGroup "semantic" allSpecs
5758

5859
-- If you're writing new test modules, please don't add to this
@@ -61,15 +62,15 @@ allTests session = do
6162
-- documentation: "hspec and tasty serve similar purposes; consider
6263
-- using one or the other.") Instead, create a new TestTree value
6364
-- in your spec module and add it to the above 'tests' list.
64-
legacySpecs :: TaskSession -> Spec
65-
legacySpecs args = do
65+
legacySpecs :: (?session :: TaskSession) => Spec
66+
legacySpecs = do
6667
describe "Semantic.Stat" Semantic.Stat.Spec.spec
6768
parallel $ do
68-
describe "Analysis.Go" (Analysis.Go.Spec.spec args)
69-
describe "Analysis.PHP" (Analysis.PHP.Spec.spec args)
70-
describe "Analysis.Python" (Analysis.Python.Spec.spec args)
71-
describe "Analysis.Ruby" (Analysis.Ruby.Spec.spec args)
72-
describe "Analysis.TypeScript" (Analysis.TypeScript.Spec.spec args)
69+
describe "Analysis.Go" Analysis.Go.Spec.spec
70+
describe "Analysis.PHP" Analysis.PHP.Spec.spec
71+
describe "Analysis.Python" Analysis.Python.Spec.spec
72+
describe "Analysis.Ruby" Analysis.Ruby.Spec.spec
73+
describe "Analysis.TypeScript" Analysis.TypeScript.Spec.spec
7374
describe "Assigning.Assignment" Assigning.Assignment.Spec.spec
7475
describe "Control.Abstract.Evaluator" Control.Abstract.Evaluator.Spec.spec
7576
describe "Data.Diff" Data.Diff.Spec.spec
@@ -101,6 +102,6 @@ legacySpecs args = do
101102
main :: IO ()
102103
main = do
103104
withOptions defaultOptions { optionsLogLevel = Nothing } $ \ config logger statter ->
104-
let session = TaskSession config "-" False logger statter
105-
in allTests session >>= defaultMain
105+
let ?session = TaskSession config "-" False logger statter
106+
in allTests >>= defaultMain
106107

0 commit comments

Comments
 (0)