1
1
mirror of https://github.com/github/semantic.git synced 2024-12-25 16:02:43 +03:00

Rename parseDiffAndRenderBlobPair to diffBlobPair.

This commit is contained in:
Rob Rix 2017-05-31 12:27:21 -04:00
parent fc536d8402
commit 4b5ad434e8
5 changed files with 15 additions and 15 deletions

View File

@ -1,7 +1,7 @@
{-# LANGUAGE GADTs #-}
module Semantic
( parseBlob
, parseDiffAndRenderBlobPair
, diffBlobPair
, diffAndRenderTermPair
) where
@ -43,8 +43,8 @@ parseBlob renderer blob@SourceBlob{..} = case renderer of
-- | A task to parse a pair of 'SourceBlob's, diff them, and render the 'Diff'.
parseDiffAndRenderBlobPair :: DiffRenderer output -> Both SourceBlob -> Task (Maybe output)
parseDiffAndRenderBlobPair renderer blobs = case renderer of
diffBlobPair :: DiffRenderer output -> Both SourceBlob -> Task (Maybe output)
diffBlobPair renderer blobs = case renderer of
ToCDiffRenderer -> do
terms <- distributeFor blobs $ \ blob -> do
term <- parseSource blob

View File

@ -21,7 +21,7 @@ import System.FilePath.Posix (takeFileName, (-<.>))
import System.IO.Error (IOError)
import System.IO (stdin)
import Text.Regex
import qualified Semantic (parseBlob, parseDiffAndRenderBlobPair)
import qualified Semantic (parseBlob, diffBlobPair)
main :: IO ()
main = do
@ -54,7 +54,7 @@ runDiff DiffArguments{..} = do
DiffPaths a b -> pure <$> traverse (uncurry readFile) (both a b)
DiffCommits sha1 sha2 paths -> readFilesAtSHAs gitDir alternateObjectDirs paths (both sha1 sha2)
DiffStdin -> readBlobPairsFromHandle stdin
Task.runTask . fmap toS $ Task.distributeFoldMap (fmap (fromMaybe mempty) . Semantic.parseDiffAndRenderBlobPair diffRenderer) blobs
Task.runTask . fmap toS $ Task.distributeFoldMap (fmap (fromMaybe mempty) . Semantic.diffBlobPair diffRenderer) blobs
runParse :: ParseArguments -> IO ByteString
runParse ParseArguments{..} = do

View File

@ -138,4 +138,4 @@ data Fixture = Fixture { shas :: Both String, expectedBlobs :: [Both SourceBlob]
fetchDiffsOutput :: FilePath -> String -> String -> [(FilePath, Maybe Language)] -> IO Summaries
fetchDiffsOutput gitDir sha1 sha2 filePaths = do
blobPairs <- runCommand $ readFilesAtSHAs gitDir [] filePaths (both sha1 sha2)
fromMaybe mempty <$> runTask (distributeFoldMap (Semantic.parseDiffAndRenderBlobPair Renderer.ToCDiffRenderer) blobPairs)
fromMaybe mempty <$> runTask (distributeFoldMap (Semantic.diffBlobPair Renderer.ToCDiffRenderer) blobPairs)

View File

@ -27,7 +27,7 @@ import Term
diffFilePaths :: Both FilePath -> IO ByteString
diffFilePaths paths = do
blobs <- traverse readFile paths
fromMaybe mempty <$> runTask (parseDiffAndRenderBlobPair SExpressionDiffRenderer blobs)
fromMaybe mempty <$> runTask (diffBlobPair SExpressionDiffRenderer blobs)
-- | Returns an s-expression parse tree for the specified FilePath.
parseFilePath :: FilePath -> IO ByteString

View File

@ -58,7 +58,7 @@ spec = parallel $ do
it "summarizes changed methods" $ do
sourceBlobs <- blobsForPaths (both "ruby/methods.A.rb" "ruby/methods.B.rb")
Just diff <- runTask (parseDiffAndRenderBlobPair IdentityDiffRenderer sourceBlobs)
Just diff <- runTask (diffBlobPair IdentityDiffRenderer sourceBlobs)
diffTOC diff `shouldBe`
[ JSONSummary $ Summarizable C.SingletonMethod "self.foo" (sourceSpanBetween (1, 1) (2, 4)) "added"
, JSONSummary $ Summarizable C.Method "bar" (sourceSpanBetween (4, 1) (6, 4)) "modified"
@ -66,31 +66,31 @@ spec = parallel $ do
it "dedupes changes in same parent method" $ do
sourceBlobs <- blobsForPaths (both "javascript/duplicate-parent.A.js" "javascript/duplicate-parent.B.js")
Just diff <- runTask (parseDiffAndRenderBlobPair IdentityDiffRenderer sourceBlobs)
Just diff <- runTask (diffBlobPair IdentityDiffRenderer sourceBlobs)
diffTOC diff `shouldBe`
[ JSONSummary $ Summarizable C.Function "myFunction" (sourceSpanBetween (1, 1) (6, 2)) "modified" ]
it "dedupes similar methods" $ do
sourceBlobs <- blobsForPaths (both "javascript/erroneous-duplicate-method.A.js" "javascript/erroneous-duplicate-method.B.js")
Just diff <- runTask (parseDiffAndRenderBlobPair IdentityDiffRenderer sourceBlobs)
Just diff <- runTask (diffBlobPair IdentityDiffRenderer sourceBlobs)
diffTOC diff `shouldBe`
[ JSONSummary $ Summarizable C.Function "performHealthCheck" (sourceSpanBetween (8, 1) (29, 2)) "modified" ]
it "summarizes Go methods with receivers with special formatting" $ do
sourceBlobs <- blobsForPaths (both "go/method-with-receiver.A.go" "go/method-with-receiver.B.go")
Just diff <- runTask (parseDiffAndRenderBlobPair IdentityDiffRenderer sourceBlobs)
Just diff <- runTask (diffBlobPair IdentityDiffRenderer sourceBlobs)
diffTOC diff `shouldBe`
[ JSONSummary $ Summarizable C.Method "(*apiClient) CheckAuth" (sourceSpanBetween (3,1) (3,101)) "added" ]
it "summarizes Ruby methods that start with two identifiers" $ do
sourceBlobs <- blobsForPaths (both "ruby/method-starts-with-two-identifiers.A.rb" "ruby/method-starts-with-two-identifiers.B.rb")
Just diff <- runTask (parseDiffAndRenderBlobPair IdentityDiffRenderer sourceBlobs)
Just diff <- runTask (diffBlobPair IdentityDiffRenderer sourceBlobs)
diffTOC diff `shouldBe`
[ JSONSummary $ Summarizable C.Method "foo" (sourceSpanBetween (1, 1) (4, 4)) "modified" ]
it "handles unicode characters in file" $ do
sourceBlobs <- blobsForPaths (both "ruby/unicode.A.rb" "ruby/unicode.B.rb")
Just diff <- runTask (parseDiffAndRenderBlobPair IdentityDiffRenderer sourceBlobs)
Just diff <- runTask (diffBlobPair IdentityDiffRenderer sourceBlobs)
diffTOC diff `shouldBe`
[ JSONSummary $ Summarizable C.Method "foo" (sourceSpanBetween (6, 1) (7, 4)) "added" ]
@ -135,12 +135,12 @@ spec = parallel $ do
describe "diff with ToCDiffRenderer" $ do
it "produces JSON output" $ do
blobs <- blobsForPaths (both "ruby/methods.A.rb" "ruby/methods.B.rb")
output <- runTask (parseDiffAndRenderBlobPair ToCDiffRenderer blobs)
output <- runTask (diffBlobPair ToCDiffRenderer blobs)
fmap toS output `shouldBe` Just ("{\"changes\":{\"test/fixtures/toc/ruby/methods.A.rb -> test/fixtures/toc/ruby/methods.B.rb\":[{\"span\":{\"start\":[1,1],\"end\":[2,4]},\"category\":\"Method\",\"term\":\"self.foo\",\"changeType\":\"added\"},{\"span\":{\"start\":[4,1],\"end\":[6,4]},\"category\":\"Method\",\"term\":\"bar\",\"changeType\":\"modified\"},{\"span\":{\"start\":[4,1],\"end\":[5,4]},\"category\":\"Method\",\"term\":\"baz\",\"changeType\":\"removed\"}]},\"errors\":{}}\n" :: ByteString)
it "produces JSON output if there are parse errors" $ do
blobs <- blobsForPaths (both "ruby/methods.A.rb" "ruby/methods.X.rb")
output <- runTask (parseDiffAndRenderBlobPair ToCDiffRenderer blobs)
output <- runTask (diffBlobPair ToCDiffRenderer blobs)
fmap toS output `shouldBe` Just ("{\"changes\":{\"test/fixtures/toc/ruby/methods.A.rb -> test/fixtures/toc/ruby/methods.X.rb\":[{\"span\":{\"start\":[4,1],\"end\":[5,4]},\"category\":\"Method\",\"term\":\"baz\",\"changeType\":\"removed\"}]},\"errors\":{\"test/fixtures/toc/ruby/methods.A.rb -> test/fixtures/toc/ruby/methods.X.rb\":[{\"span\":{\"start\":[1,1],\"end\":[3,1]},\"error\":\"def bar\\nen\\n\"}]}}\n" :: ByteString)
type Diff' = SyntaxDiff Text (Maybe Declaration ': DefaultFields)