diff --git a/test/Analysis/PHP/Spec.hs b/test/Analysis/PHP/Spec.hs index ac1e096cdc..b59418c842 100644 --- a/test/Analysis/PHP/Spec.hs +++ b/test/Analysis/PHP/Spec.hs @@ -32,7 +32,7 @@ spec = parallel $ do xit "evaluates namespaces" $ do (scopeGraph, (heap, res)) <- evaluate ["namespaces.php"] case ModuleTable.lookup "namespaces.php" <$> res of - Right (Just (Module _ (scopeAndFrame, value))) -> do + Right (Just (Module _ (scopeAndFrame, _))) -> do const () <$> SpecHelpers.lookupDeclaration "Foo" scopeAndFrame heap scopeGraph `shouldBe` Just () const () <$> SpecHelpers.lookupDeclaration "NS1" scopeAndFrame heap scopeGraph `shouldBe` Just () diff --git a/test/Analysis/Python/Spec.hs b/test/Analysis/Python/Spec.hs index 122c6985b3..9d43baf0da 100644 --- a/test/Analysis/Python/Spec.hs +++ b/test/Analysis/Python/Spec.hs @@ -27,7 +27,7 @@ spec = parallel $ do it "imports with aliases" $ do (scopeGraph, (heap, res)) <- evaluate ["main1.py", "a.py", "b/__init__.py", "b/c.py"] case ModuleTable.lookup "main1.py" <$> res of - Right (Just (Module _ (scopeAndFrame, value))) -> do + Right (Just (Module _ (scopeAndFrame, _))) -> do const () <$> SpecHelpers.lookupDeclaration "b" scopeAndFrame heap scopeGraph `shouldBe` Just () const () <$> SpecHelpers.lookupDeclaration "e" scopeAndFrame heap scopeGraph `shouldBe` Just () other -> expectationFailure (show other) @@ -35,7 +35,7 @@ spec = parallel $ do it "imports using from syntax" $ do (scopeGraph, (heap, res)) <- evaluate ["main2.py", "a.py", "b/__init__.py", "b/c.py"] case ModuleTable.lookup "main2.py" <$> res of - Right (Just (Module _ (scopeAndFrame, value))) -> do + Right (Just (Module _ (scopeAndFrame, _))) -> do const () <$> SpecHelpers.lookupDeclaration "bar" scopeAndFrame heap scopeGraph `shouldBe` Just () const () <$> SpecHelpers.lookupDeclaration "foo" scopeAndFrame heap scopeGraph `shouldBe` Just () @@ -46,7 +46,7 @@ spec = parallel $ do it "imports with relative syntax" $ do (scopeGraph, (heap, res)) <- evaluate ["main3.py", "c/__init__.py", "c/utils.py"] case ModuleTable.lookup "main3.py" <$> res of - Right (Just (Module _ (scopeAndFrame, value))) -> do + Right (Just (Module _ (scopeAndFrame, _))) -> do const () <$> SpecHelpers.lookupDeclaration "utils" scopeAndFrame heap scopeGraph `shouldBe` Just () -- (lookupDeclaration "utils" heap >>= deNamespace heap) `shouldBe` Just ("utils", ["to_s"]) other -> expectationFailure (show other) diff --git a/test/Analysis/Ruby/Spec.hs b/test/Analysis/Ruby/Spec.hs index e2c4cac4d5..3e9208c3c1 100644 --- a/test/Analysis/Ruby/Spec.hs +++ b/test/Analysis/Ruby/Spec.hs @@ -50,7 +50,7 @@ spec = parallel $ do it "evaluates modules" $ do (scopeGraph, (heap, res)) <- evaluate ["modules.rb"] case ModuleTable.lookup "modules.rb" <$> res of - Right (Just (Module _ (scopeAndFrame, value))) -> do + Right (Just (Module _ (scopeAndFrame, _))) -> do const () <$> SpecHelpers.lookupDeclaration "Bar" scopeAndFrame heap scopeGraph `shouldBe` Just () other -> expectationFailure (show other) diff --git a/test/Analysis/TypeScript/Spec.hs b/test/Analysis/TypeScript/Spec.hs index da7ebb636c..a0e9db641b 100644 --- a/test/Analysis/TypeScript/Spec.hs +++ b/test/Analysis/TypeScript/Spec.hs @@ -74,7 +74,7 @@ spec = parallel $ do it "side effect only imports dont expose exports" $ do (scopeGraph, (heap, res)) <- evaluate ["main3.ts", "a.ts"] case ModuleTable.lookup "main3.ts" <$> res of - Right (Just (Module _ (scopeAndFrame@(currentScope, currentFrame), value))) -> do + Right (Just (Module _ (scopeAndFrame, value))) -> do () <$ SpecHelpers.lookupDeclaration "baz" scopeAndFrame heap scopeGraph `shouldBe` Nothing value `shouldBe` Unit Heap.heapSize heap `shouldBe` 4 @@ -87,14 +87,14 @@ spec = parallel $ do it "evaluates early return statements" $ do (scopeGraph, (heap, res)) <- evaluate ["early-return.ts"] case ModuleTable.lookup "early-return.ts" <$> res of - Right (Just (Module _ (scopeAndFrame, value))) -> + Right (Just (Module _ (scopeAndFrame, _))) -> const () <$> SpecHelpers.lookupDeclaration "foo" scopeAndFrame heap scopeGraph `shouldBe` Just () other -> expectationFailure (show other) it "evaluates sequence expressions" $ do (scopeGraph, (heap, res)) <- evaluate ["sequence-expression.ts"] case ModuleTable.lookup "sequence-expression.ts" <$> res of - Right (Just (Module _ (scopeAndFrame, value))) -> + Right (Just (Module _ (scopeAndFrame, _))) -> SpecHelpers.lookupDeclaration "x" scopeAndFrame heap scopeGraph `shouldBe` Just [ Concrete.Float (Number.Decimal (scientific 3 0)) ] other -> expectationFailure (show other) @@ -115,7 +115,7 @@ spec = parallel $ do it "evaluates await" $ do (scopeGraph, (heap, res)) <- evaluate ["await.ts"] case ModuleTable.lookup "await.ts" <$> res of - Right (Just (Module _ (scopeAndFrame, value))) -> do + Right (Just (Module _ (scopeAndFrame, _))) -> do -- Test that f2 is in the scopegraph and heap. const () <$> SpecHelpers.lookupDeclaration "f2" scopeAndFrame heap scopeGraph `shouldBe` Just () -- Test we can't reference y from outside the function @@ -159,7 +159,7 @@ spec = parallel $ do other -> expectationFailure (show other) it "uniquely tracks public fields for instances" $ do - (scopeGraph, (heap, res)) <- evaluate ["class1.ts", "class2.ts"] + (_, (_, res)) <- evaluate ["class1.ts", "class2.ts"] case ModuleTable.lookup "class1.ts" <$> res of Right (Just (Module _ (_, value))) -> value `shouldBe` (Concrete.Float (Number.Decimal 9.0)) other -> expectationFailure (show other) diff --git a/test/Data/Abstract/Name/Spec.hs b/test/Data/Abstract/Name/Spec.hs index 972266b341..d95496470a 100644 --- a/test/Data/Abstract/Name/Spec.hs +++ b/test/Data/Abstract/Name/Spec.hs @@ -1,4 +1,4 @@ -module Data.Abstract.Name.Spec where +module Data.Abstract.Name.Spec (spec) where import SpecHelpers diff --git a/test/Data/Functor/Listable.hs b/test/Data/Functor/Listable.hs index ee74ea0819..8f69b5926d 100644 --- a/test/Data/Functor/Listable.hs +++ b/test/Data/Functor/Listable.hs @@ -23,8 +23,6 @@ import Control.Monad.Free as Free import Control.Monad.Trans.Free as FreeF import Data.Abstract.ScopeGraph (AccessControl(..)) import Data.Bifunctor.Join -import Data.ByteString (ByteString) -import Data.Char (chr) import Data.Diff import Data.Functor.Both import qualified Data.Language as Language @@ -32,10 +30,7 @@ import Data.List.NonEmpty import Data.Patch import Data.Range import Data.Location -import Data.Semigroup (Semigroup(..)) import Data.Semigroup.App -import Data.Source -import Data.Blob import Data.Span import qualified Data.Syntax as Syntax import qualified Data.Syntax.Literal as Literal @@ -49,7 +44,6 @@ import qualified Language.Python.Syntax as Python.Syntax import qualified Data.Abstract.Name as Name import Data.Term import Data.Text as T (Text, pack) -import qualified Data.Text.Encoding as T import Data.These import Data.Sum import Diffing.Algorithm.RWS @@ -265,28 +259,28 @@ instance Listable1 Literal.Array where liftTiers tiers = liftCons1 (liftTiers tiers) Literal.Array instance Listable1 Literal.Boolean where - liftTiers tiers = cons1 Literal.Boolean + liftTiers _ = cons1 Literal.Boolean instance Listable1 Literal.Hash where liftTiers tiers = liftCons1 (liftTiers tiers) Literal.Hash instance Listable1 Literal.Float where - liftTiers tiers = cons1 Literal.Float + liftTiers _ = cons1 Literal.Float instance Listable1 Literal.Null where - liftTiers tiers = cons0 Literal.Null + liftTiers _ = cons0 Literal.Null instance Listable1 Literal.TextElement where - liftTiers tiers = cons1 Literal.TextElement + liftTiers _ = cons1 Literal.TextElement instance Listable1 Literal.EscapeSequence where - liftTiers tiers = cons1 Literal.EscapeSequence + liftTiers _ = cons1 Literal.EscapeSequence instance Listable1 Literal.InterpolationElement where liftTiers tiers = liftCons1 tiers Literal.InterpolationElement instance Listable1 Literal.Character where - liftTiers tiers = cons1 Literal.Character + liftTiers _ = cons1 Literal.Character instance Listable1 Statement.Statements where liftTiers tiers = liftCons1 (liftTiers tiers) Statement.Statements @@ -295,10 +289,10 @@ instance Listable1 Syntax.Error where liftTiers tiers = liftCons4 mempty mempty mempty (liftTiers tiers) Syntax.Error instance Listable1 Directive.File where - liftTiers tiers = cons0 Directive.File + liftTiers _ = cons0 Directive.File instance Listable1 Directive.Line where - liftTiers tiers = cons0 Directive.Line + liftTiers _ = cons0 Directive.Line instance Listable1 Expression.Plus where liftTiers tiers = liftCons2 tiers tiers Expression.Plus @@ -403,19 +397,19 @@ instance Listable1 Expression.Member where liftTiers tiers = liftCons2 tiers tiers Expression.Member instance Listable1 Expression.This where - liftTiers tiers = cons0 Expression.This + liftTiers _ = cons0 Expression.This instance Listable1 Literal.Complex where - liftTiers tiers = cons1 Literal.Complex + liftTiers _ = cons1 Literal.Complex instance Listable1 Literal.Integer where - liftTiers tiers = cons1 Literal.Integer + liftTiers _ = cons1 Literal.Integer instance Listable1 Literal.Rational where - liftTiers tiers = cons1 Literal.Rational + liftTiers _ = cons1 Literal.Rational instance Listable1 Literal.Regex where - liftTiers tiers = cons1 Literal.Regex + liftTiers _ = cons1 Literal.Regex instance Listable1 Literal.String where liftTiers tiers = liftCons1 (liftTiers tiers) Literal.String @@ -424,7 +418,7 @@ instance Listable1 Literal.Symbol where liftTiers tiers = liftCons1 (liftTiers tiers) Literal.Symbol instance Listable1 Literal.SymbolElement where - liftTiers tiers = cons1 Literal.SymbolElement + liftTiers _ = cons1 Literal.SymbolElement instance Listable1 Statement.Assignment where liftTiers tiers = liftCons3 (liftTiers tiers) tiers tiers Statement.Assignment @@ -493,7 +487,7 @@ instance Listable1 Ruby.Syntax.Require where liftTiers tiers' = liftCons2 tiers tiers' Ruby.Syntax.Require instance Listable1 Ruby.Syntax.ZSuper where - liftTiers tiers = cons0 Ruby.Syntax.ZSuper + liftTiers _ = cons0 Ruby.Syntax.ZSuper instance Listable1 Ruby.Syntax.Send where liftTiers tiers = liftCons4 (liftTiers tiers) (liftTiers tiers) (liftTiers tiers) (liftTiers tiers) Ruby.Syntax.Send diff --git a/test/Data/Graph/Spec.hs b/test/Data/Graph/Spec.hs index 47a7496161..22843514c0 100644 --- a/test/Data/Graph/Spec.hs +++ b/test/Data/Graph/Spec.hs @@ -1,6 +1,6 @@ {-# LANGUAGE PackageImports #-} -module Data.Graph.Spec where +module Data.Graph.Spec (spec) where import SpecHelpers diff --git a/test/Data/Range/Spec.hs b/test/Data/Range/Spec.hs index b6c4e2af2d..2556250541 100644 --- a/test/Data/Range/Spec.hs +++ b/test/Data/Range/Spec.hs @@ -1,6 +1,6 @@ {-# LANGUAGE ScopedTypeVariables #-} -module Data.Range.Spec where +module Data.Range.Spec (spec) where import Data.Range import SpecHelpers diff --git a/test/Data/Scientific/Spec.hs b/test/Data/Scientific/Spec.hs index cdfd3d9810..894173964f 100644 --- a/test/Data/Scientific/Spec.hs +++ b/test/Data/Scientific/Spec.hs @@ -1,4 +1,4 @@ -module Data.Scientific.Spec where +module Data.Scientific.Spec (spec) where import Data.Scientific.Exts import Data.Either diff --git a/test/Data/Semigroup/App/Spec.hs b/test/Data/Semigroup/App/Spec.hs index e3acf4bc1c..eb4aafe1ad 100644 --- a/test/Data/Semigroup/App/Spec.hs +++ b/test/Data/Semigroup/App/Spec.hs @@ -1,4 +1,4 @@ -module Data.Semigroup.App.Spec where +module Data.Semigroup.App.Spec (spec) where import SpecHelpers import Data.Semigroup.App diff --git a/test/Graphing/Calls/Spec.hs b/test/Graphing/Calls/Spec.hs index 7f43422507..b9b250aeb2 100644 --- a/test/Graphing/Calls/Spec.hs +++ b/test/Graphing/Calls/Spec.hs @@ -13,6 +13,7 @@ import Data.Graph.ControlFlowVertex import qualified Data.Language as Language import Semantic.Graph +callGraphPythonProject :: [FilePath] -> IO (Semantic.Graph.Graph ControlFlowVertex) callGraphPythonProject paths = runTaskOrDie $ do let proxy = Proxy @'Language.Python let lang = Language.Python diff --git a/test/Parsing/Spec.hs b/test/Parsing/Spec.hs index d0e6ebc5cf..f8e9616556 100644 --- a/test/Parsing/Spec.hs +++ b/test/Parsing/Spec.hs @@ -14,7 +14,7 @@ import TreeSitter.JSON (tree_sitter_json, Grammar) spec :: Spec spec = parallel $ do describe "parseToAST" $ do - let source = toJSONSource $ take 10000 [1..] + let source = toJSONSource [1 :: Int .. 10000] let largeBlob = sourceBlob "large.json" JSON source it "returns a result when the timeout does not expire" $ do diff --git a/test/Reprinting/Spec.hs b/test/Reprinting/Spec.hs index 0675cdca50..549257b402 100644 --- a/test/Reprinting/Spec.hs +++ b/test/Reprinting/Spec.hs @@ -1,6 +1,6 @@ {-# LANGUAGE GADTs, OverloadedLists, TypeOperators #-} -module Reprinting.Spec where +module Reprinting.Spec (spec) where import SpecHelpers @@ -59,7 +59,11 @@ spec = describe "reprinting" $ do printed `shouldBe` Right src it "should be able to parse the output of a refactor" $ do - let (Just tagged) = rewrite (mark Unmodified tree) (topDownAny increaseNumbers) - let (Right printed) = runReprinter src defaultJSONPipeline tagged + let maybeTagged = rewrite (mark Unmodified tree) (topDownAny increaseNumbers) + tagged <- maybe (fail "rewrite failed") pure maybeTagged + + let eitherPrinted = runReprinter src defaultJSONPipeline tagged + printed <- either (fail "reprinter failed") pure eitherPrinted + tree' <- runTaskOrDie (parse jsonParser (makeBlob printed path Language.JSON mempty)) length tree' `shouldSatisfy` (/= 0) diff --git a/test/Semantic/CLI/Spec.hs b/test/Semantic/CLI/Spec.hs index 923d3afce0..7cef8c864d 100644 --- a/test/Semantic/CLI/Spec.hs +++ b/test/Semantic/CLI/Spec.hs @@ -30,6 +30,7 @@ renderDiff ref new = unsafePerformIO $ do else ["git", "diff", ref, new] {-# NOINLINE renderDiff #-} +testForDiffFixture :: (String, [BlobPair] -> TaskEff Builder, [Both File], FilePath) -> TestTree testForDiffFixture (diffRenderer, runDiff, files, expected) = goldenVsStringDiff ("diff fixture renders to " <> diffRenderer <> " " <> show files) @@ -37,6 +38,7 @@ testForDiffFixture (diffRenderer, runDiff, files, expected) = expected (fmap toLazyByteString . runTaskOrDie $ readBlobPairs (Right files) >>= runDiff) +testForParseFixture :: (String, [Blob] -> TaskEff Builder, [File], FilePath) -> TestTree testForParseFixture (format, runParse, files, expected) = goldenVsStringDiff ("diff fixture renders to " <> format <> " " <> show files) diff --git a/test/Spec.hs b/test/Spec.hs index e17aab4383..d5ff3ab7ce 100644 --- a/test/Spec.hs +++ b/test/Spec.hs @@ -1,6 +1,6 @@ {-# LANGUAGE ImplicitParams #-} -module Main where +module Main (allTests, legacySpecs, main, tests) where import qualified Analysis.Go.Spec import qualified Analysis.PHP.Spec @@ -105,4 +105,3 @@ main = do withOptions defaultOptions { optionsLogLevel = Nothing } $ \ config logger statter -> let ?session = TaskSession config "-" False logger statter in allTests >>= defaultMain - diff --git a/test/SpecHelpers.hs b/test/SpecHelpers.hs index c18f7ad8cb..443f0dc0ba 100644 --- a/test/SpecHelpers.hs +++ b/test/SpecHelpers.hs @@ -35,7 +35,7 @@ import Data.Abstract.Name as X import Data.Abstract.Value.Concrete (Value(..), ValueError, runValueError) import Data.Blob as X import Data.Blob.IO as X -import Data.ByteString.Builder (toLazyByteString) +import Data.ByteString.Builder (Builder, toLazyByteString) import Data.ByteString.Lazy (toStrict) import Data.Project as X import Data.Proxy as X @@ -75,6 +75,7 @@ import Semantic.Api hiding (File, Blob, BlobPair) import System.Exit (die) import Control.Exception (displayException) +runBuilder :: Builder -> ByteString runBuilder = toStrict . toLazyByteString -- | This orphan instance is so we don't have to insert @name@ calls