1
1
mirror of https://github.com/github/semantic.git synced 2024-12-19 04:41:47 +03:00
semantic/test/Rendering/TOC/Spec.hs

224 lines
12 KiB
Haskell
Raw Normal View History

{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE MonoLocalBinds #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE TypeOperators #-}
module Rendering.TOC.Spec (spec) where
import Analysis.TOCSummary
import Control.Effect.Parse
import Control.Monad.IO.Class
import Data.Aeson hiding (defaultOptions)
import Data.Bifunctor
import Data.Diff
import Data.Either (isRight)
import Data.Sum
2018-03-13 20:59:20 +03:00
import qualified Data.Syntax as Syntax
import qualified Data.Syntax.Declaration as Declaration
import Data.Term
import Data.Text (Text)
import Diffing.Interpreter
import Prelude
import Rendering.TOC
import Semantic.Api (diffSummaryBuilder, summarizeTermParsers, summarizeTerms)
import Serializing.Format as Format
import Source.Loc
import Source.Span
import System.Path ((</>))
import qualified System.Path as Path
2018-03-13 20:59:20 +03:00
2017-05-11 17:00:11 +03:00
import SpecHelpers
2020-02-13 07:50:16 +03:00
don't :: Applicative m => m a -> m ()
don't = const (pure ())
spec :: Spec
2019-06-20 00:22:09 +03:00
spec = do
describe "tableOfContentsBy" $ do
prop "drops all nodes with the constant Nothing function" $
\ diff -> tableOfContentsBy (const Nothing :: a -> Maybe ()) (diff :: Diff ListableSyntax () ()) `shouldBe` []
prop "produces no entries for identity diffs" $
\ term -> tableOfContentsBy (Just . termFAnnotation) (diffTerms term (term :: Term ListableSyntax ())) `shouldBe` []
2017-05-11 23:37:08 +03:00
prop "produces inserted/deleted/replaced entries for relevant nodes within patches" $
2019-10-21 19:03:07 +03:00
\ p -> tableOfContentsBy (Just . termFAnnotation) (edit deleting inserting comparing p)
`shouldBe`
2019-10-21 19:03:07 +03:00
edit (fmap (Deleted,)) (fmap (Inserted,)) (\ as bs -> (Replaced, head bs) : fmap (Deleted,) (tail as) <> fmap (Inserted,) (tail bs)) (bimap (foldMap pure) (foldMap pure) (p :: Edit (Term ListableSyntax Int) (Term ListableSyntax Int)))
prop "produces changed entries for relevant nodes containing irrelevant patches" $
\ diff -> do
2018-05-17 01:25:02 +03:00
let diff' = merge (True, True) (inject [bimap (const False) (const False) (diff :: Diff ListableSyntax Bool Bool)])
let toc = tableOfContentsBy (\ (n `In` _) -> if n then Just n else Nothing) diff'
toc `shouldBe` if null (diffPatches diff') then []
2019-10-17 10:48:05 +03:00
else [(Changed, True)]
2017-02-23 07:05:20 +03:00
describe "diffTOC" $ do
it "blank if there are no methods" $
2017-07-20 03:01:59 +03:00
diffTOC blankDiff `shouldBe` [ ]
it "summarizes changed methods" $ do
2019-10-18 17:45:59 +03:00
sourceBlobs <- blobsForPaths (Path.relFile "ruby/toc/methods.A.rb") (Path.relFile "ruby/toc/methods.B.rb")
2019-10-17 11:13:55 +03:00
diff <- runTaskOrDie $ summarize sourceBlobs
diff `shouldBe`
2019-10-17 10:51:31 +03:00
[ Right $ TOCSummary (Method (Just "self")) "self.foo" (Span (Pos 1 1) (Pos 2 4)) Inserted
2019-10-17 10:48:05 +03:00
, Right $ TOCSummary (Method Nothing) "bar" (Span (Pos 4 1) (Pos 6 4)) Changed
, Right $ TOCSummary (Method Nothing) "baz" (Span (Pos 4 1) (Pos 5 4)) Deleted
]
2017-02-14 22:53:25 +03:00
it "dedupes changes in same parent method" $ do
2019-10-18 17:45:59 +03:00
sourceBlobs <- blobsForPaths (Path.relFile "javascript/toc/duplicate-parent.A.js") (Path.relFile "javascript/toc/duplicate-parent.B.js")
2019-10-17 11:13:55 +03:00
diff <- runTaskOrDie $ summarize sourceBlobs
diff `shouldBe`
2019-10-17 10:48:05 +03:00
[ Right $ TOCSummary Function "myFunction" (Span (Pos 1 1) (Pos 6 2)) Changed ]
2017-02-14 22:53:25 +03:00
it "dedupes similar methods" $ do
2019-10-18 17:45:59 +03:00
sourceBlobs <- blobsForPaths (Path.relFile "javascript/toc/erroneous-duplicate-method.A.js") (Path.relFile "javascript/toc/erroneous-duplicate-method.B.js")
2019-10-17 11:13:55 +03:00
diff <- runTaskOrDie $ summarize sourceBlobs
diff `shouldBe`
2019-10-17 10:51:31 +03:00
[ Right $ TOCSummary Function "performHealthCheck" (Span (Pos 8 1) (Pos 29 2)) Replaced ]
it "summarizes Go methods with receivers with special formatting" $ do
2019-10-18 17:45:59 +03:00
sourceBlobs <- blobsForPaths (Path.relFile "go/toc/method-with-receiver.A.go") (Path.relFile "go/toc/method-with-receiver.B.go")
2019-10-17 11:13:55 +03:00
diff <- runTaskOrDie $ summarize sourceBlobs
diff `shouldBe`
2019-10-17 10:51:31 +03:00
[ Right $ TOCSummary (Method (Just "*apiClient")) "(*apiClient) CheckAuth" (Span (Pos 3 1) (Pos 3 101)) Inserted ]
it "summarizes Ruby methods that start with two identifiers" $ do
2019-10-18 17:45:59 +03:00
sourceBlobs <- blobsForPaths (Path.relFile "ruby/toc/method-starts-with-two-identifiers.A.rb") (Path.relFile "ruby/toc/method-starts-with-two-identifiers.B.rb")
2019-10-17 11:13:55 +03:00
diff <- runTaskOrDie $ summarize sourceBlobs
diff `shouldBe`
2019-10-17 10:48:05 +03:00
[ Right $ TOCSummary (Method Nothing) "foo" (Span (Pos 1 1) (Pos 4 4)) Changed ]
it "handles unicode characters in file" $ do
2019-10-18 17:45:59 +03:00
sourceBlobs <- blobsForPaths (Path.relFile "ruby/toc/unicode.A.rb") (Path.relFile "ruby/toc/unicode.B.rb")
2019-10-17 11:13:55 +03:00
diff <- runTaskOrDie $ summarize sourceBlobs
diff `shouldBe`
2019-10-17 10:48:05 +03:00
[ Right $ TOCSummary (Method Nothing) "foo" (Span (Pos 6 1) (Pos 7 4)) Inserted ]
it "properly slices source blob that starts with a newline and has multi-byte chars" $ do
2019-10-18 17:45:59 +03:00
sourceBlobs <- blobsForPaths (Path.relFile "javascript/toc/starts-with-newline.js") (Path.relFile "javascript/toc/starts-with-newline.js")
2019-10-17 11:13:55 +03:00
diff <- runTaskOrDie $ summarize sourceBlobs
diff `shouldBe` []
2017-11-22 18:17:32 +03:00
prop "inserts of methods and functions are summarized" . forAll ((not . isMethodOrFunction . Prelude.snd) `filterT` tiers) $
\(name, body) ->
2017-09-09 16:18:08 +03:00
let diff = programWithInsert name body
in numTocSummaries diff `shouldBe` 1
2017-02-16 23:23:40 +03:00
2017-11-22 18:17:32 +03:00
prop "deletes of methods and functions are summarized" . forAll ((not . isMethodOrFunction . Prelude.snd) `filterT` tiers) $
\(name, body) ->
2017-09-09 16:18:08 +03:00
let diff = programWithDelete name body
in numTocSummaries diff `shouldBe` 1
2017-11-22 18:17:32 +03:00
prop "replacements of methods and functions are summarized" . forAll ((not . isMethodOrFunction . Prelude.snd) `filterT` tiers) $
\(name, body) ->
2017-09-09 16:18:08 +03:00
let diff = programWithReplace name body
in numTocSummaries diff `shouldBe` 1
2017-11-22 18:17:32 +03:00
prop "changes inside methods and functions are summarizied" . forAll (((&&) <$> not . isMethodOrFunction <*> isMeaningfulTerm) `filterT` tiers) $
\body ->
2017-09-09 16:18:08 +03:00
let diff = programWithChange body
in numTocSummaries diff `shouldBe` 1
prop "other changes don't summarize" . forAll ((not . isMethodOrFunction) `filterT` tiers) $
\body ->
2017-09-09 16:18:08 +03:00
let diff = programWithChangeOutsideFunction body
in numTocSummaries diff `shouldBe` 0
prop "unchanged diffs arent summarized" $
\term -> diffTOC (diffTerms term (term :: Term')) `shouldBe` []
2017-10-27 21:15:46 +03:00
describe "TOCSummary" $ do
2017-06-05 18:32:18 +03:00
it "encodes modified summaries to JSON" $ do
2019-10-17 10:48:05 +03:00
let summary = TOCSummary (Method Nothing) "foo" (Span (Pos 1 1) (Pos 4 4)) Changed
2017-02-23 07:05:20 +03:00
encode summary `shouldBe` "{\"span\":{\"start\":[1,1],\"end\":[4,4]},\"category\":\"Method\",\"term\":\"foo\",\"changeType\":\"modified\"}"
2017-06-05 18:32:18 +03:00
it "encodes added summaries to JSON" $ do
2019-10-17 10:48:05 +03:00
let summary = TOCSummary (Method Nothing) "self.foo" (Span (Pos 1 1) (Pos 2 4)) Inserted
2017-02-23 07:05:20 +03:00
encode summary `shouldBe` "{\"span\":{\"start\":[1,1],\"end\":[2,4]},\"category\":\"Method\",\"term\":\"self.foo\",\"changeType\":\"added\"}"
2019-10-11 17:07:58 +03:00
describe "diff with diffSummaryBuilder" $ do
it "produces JSON output" $ do
2019-10-18 17:45:59 +03:00
blobs <- blobsForPaths (Path.relFile "ruby/toc/methods.A.rb") (Path.relFile "ruby/toc/methods.B.rb")
2020-01-24 21:26:45 +03:00
output <- runTaskOrDie (runReader aLaCarteLanguageModes (diffSummaryBuilder Format.JSON [blobs]))
2019-03-12 01:32:15 +03:00
runBuilder output `shouldBe` ("{\"files\":[{\"path\":\"test/fixtures/ruby/toc/methods.A.rb -> test/fixtures/ruby/toc/methods.B.rb\",\"language\":\"Ruby\",\"changes\":[{\"category\":\"Method\",\"term\":\"self.foo\",\"span\":{\"start\":{\"line\":1,\"column\":1},\"end\":{\"line\":2,\"column\":4}},\"changeType\":\"ADDED\"},{\"category\":\"Method\",\"term\":\"bar\",\"span\":{\"start\":{\"line\":4,\"column\":1},\"end\":{\"line\":6,\"column\":4}},\"changeType\":\"MODIFIED\"},{\"category\":\"Method\",\"term\":\"baz\",\"span\":{\"start\":{\"line\":4,\"column\":1},\"end\":{\"line\":5,\"column\":4}},\"changeType\":\"REMOVED\"}]}]}\n" :: ByteString)
2017-02-23 07:05:20 +03:00
2020-02-13 07:50:16 +03:00
it "[DISABLED] produces JSON output if there are parse errors" . don't $ do
2019-10-18 17:45:59 +03:00
blobs <- blobsForPaths (Path.relFile "ruby/toc/methods.A.rb") (Path.relFile "ruby/toc/methods.X.rb")
2019-10-18 02:31:46 +03:00
output <- runTaskOrDie (runReader defaultLanguageModes (diffSummaryBuilder Format.JSON [blobs]))
2020-01-28 03:06:49 +03:00
runBuilder output `shouldBe` ("{\"files\":[{\"path\":\"test/fixtures/ruby/toc/methods.A.rb -> test/fixtures/ruby/toc/methods.X.rb\",\"language\":\"Ruby\",\"changes\":[{\"category\":\"Method\",\"term\":\"bar\",\"span\":{\"start\":{\"line\":1,\"column\":1},\"end\":{\"line\":2,\"column\":4}},\"changeType\":\"REMOVED\"},{\"category\":\"Method\",\"term\":\"baz\",\"span\":{\"start\":{\"line\":4,\"column\":1},\"end\":{\"line\":5,\"column\":4}},\"changeType\":\"REMOVED\"}],\"errors\":[{\"error\":\"expected end of input nodes, but got ParseError\",\"span\":{\"start\":{\"line\":1,\"column\":1},\"end\":{\"line\":3,\"column\":1}}}]}]}\n" :: ByteString)
2017-02-23 07:05:20 +03:00
it "ignores anonymous functions" $ do
2019-10-18 17:45:59 +03:00
blobs <- blobsForPaths (Path.relFile "ruby/toc/lambda.A.rb") (Path.relFile "ruby/toc/lambda.B.rb")
2020-01-24 21:26:45 +03:00
output <- runTaskOrDie (runReader aLaCarteLanguageModes (diffSummaryBuilder Format.JSON [blobs]))
2019-03-12 01:32:15 +03:00
runBuilder output `shouldBe` ("{\"files\":[{\"path\":\"test/fixtures/ruby/toc/lambda.A.rb -> test/fixtures/ruby/toc/lambda.B.rb\",\"language\":\"Ruby\"}]}\n" :: ByteString)
2017-02-23 07:05:20 +03:00
type Diff' = Diff ListableSyntax (Maybe Declaration) (Maybe Declaration)
type Term' = Term ListableSyntax (Maybe Declaration)
numTocSummaries :: Diff' -> Int
2019-10-17 10:48:05 +03:00
numTocSummaries diff = length $ filter isRight (diffTOC diff)
2019-10-18 17:36:47 +03:00
-- Return a diff where body is inserted in the expressions of a function. The function is present in both sides of the diff.
programWithChange :: Term' -> Diff'
programWithChange body = merge (Nothing, Nothing) (inject [ function' ])
where
function' = merge (Just (Declaration Function "foo" lowerBound Ruby), Just (Declaration Function "foo" lowerBound Ruby)) (inject (Declaration.Function [] name' [] (merge (Nothing, Nothing) (inject [ inserting body ]))))
name' = merge (Nothing, Nothing) (inject (Syntax.Identifier (name "foo")))
2019-10-18 17:36:47 +03:00
-- Return a diff where term is inserted in the program, below a function found on both sides of the diff.
programWithChangeOutsideFunction :: Term' -> Diff'
programWithChangeOutsideFunction term = merge (Nothing, Nothing) (inject [ function', term' ])
where
function' = merge (Nothing, Nothing) (inject (Declaration.Function [] name' [] (merge (Nothing, Nothing) (inject []))))
name' = merge (Nothing, Nothing) (inject (Syntax.Identifier (name "foo")))
2017-05-10 23:08:39 +03:00
term' = inserting term
2017-05-08 22:08:01 +03:00
programWithInsert :: Text -> Term' -> Diff'
2017-05-11 20:49:25 +03:00
programWithInsert name body = programOf $ inserting (functionOf name body)
2017-05-08 22:08:01 +03:00
programWithDelete :: Text -> Term' -> Diff'
2017-05-11 20:49:25 +03:00
programWithDelete name body = programOf $ deleting (functionOf name body)
2017-02-16 23:23:40 +03:00
2017-05-08 22:08:01 +03:00
programWithReplace :: Text -> Term' -> Diff'
2019-10-18 05:18:48 +03:00
programWithReplace name body = programOf $ comparing (functionOf name body) (functionOf (name <> "2") body)
2017-02-16 23:23:40 +03:00
2017-05-11 20:49:25 +03:00
programOf :: Diff' -> Diff'
programOf diff = merge (Nothing, Nothing) (inject [ diff ])
2017-02-16 23:23:40 +03:00
2017-05-08 22:08:01 +03:00
functionOf :: Text -> Term' -> Term'
functionOf n body = termIn (Just (Declaration Function n lowerBound Unknown)) (inject (Declaration.Function [] name' [] (termIn Nothing (inject [body]))))
where
name' = termIn Nothing (inject (Syntax.Identifier (name n)))
-- Filter tiers for terms that we consider "meaniningful" in TOC summaries.
isMeaningfulTerm :: Term ListableSyntax a -> Bool
isMeaningfulTerm a
2018-05-17 01:25:02 +03:00
| Just (_:_) <- project (termOut a) = False
| Just [] <- project (termOut a) = False
2018-09-27 00:54:48 +03:00
| otherwise = True
-- Filter tiers for terms if the Syntax is a Method or a Function.
isMethodOrFunction :: Term' -> Bool
isMethodOrFunction a
2018-05-17 01:25:02 +03:00
| Just Declaration.Method{} <- project (termOut a) = True
| Just Declaration.Function{} <- project (termOut a) = True
2018-09-27 00:54:48 +03:00
| any isJust (foldMap (:[]) a) = True
| otherwise = False
2019-10-18 17:45:59 +03:00
blobsForPaths :: Path.RelFile -> Path.RelFile -> IO BlobPair
blobsForPaths p1 p2 = readFilePathPair (prefix p1) (prefix p2) where
prefix = (Path.relDir "test/fixtures" </>)
2017-05-11 22:53:22 +03:00
blankDiff :: Diff'
blankDiff = merge (Nothing, Nothing) (inject [ inserting (termIn Nothing (inject (Syntax.Identifier (name "\"a\"")))) ])
2018-04-26 16:05:18 +03:00
-- Diff helpers
2019-10-17 11:13:55 +03:00
summarize
2019-11-09 06:48:26 +03:00
:: (Has (Error SomeException) sig m, Has Parse sig m, Has Telemetry sig m, MonadIO m)
2019-10-17 11:10:29 +03:00
=> BlobPair
-> m [Either ErrorSummary TOCSummary]
2020-01-24 21:26:45 +03:00
summarize = parsePairWith (summarizeTermParsers aLaCarteLanguageModes) summarizeTerms