mirror of
https://github.com/github/semantic.git
synced 2024-12-26 00:12:29 +03:00
Rename parseDiffAndRenderBlobPair to diffBlobPair.
This commit is contained in:
parent
fc536d8402
commit
4b5ad434e8
@ -1,7 +1,7 @@
|
|||||||
{-# LANGUAGE GADTs #-}
|
{-# LANGUAGE GADTs #-}
|
||||||
module Semantic
|
module Semantic
|
||||||
( parseBlob
|
( parseBlob
|
||||||
, parseDiffAndRenderBlobPair
|
, diffBlobPair
|
||||||
, diffAndRenderTermPair
|
, diffAndRenderTermPair
|
||||||
) where
|
) 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'.
|
-- | A task to parse a pair of 'SourceBlob's, diff them, and render the 'Diff'.
|
||||||
parseDiffAndRenderBlobPair :: DiffRenderer output -> Both SourceBlob -> Task (Maybe output)
|
diffBlobPair :: DiffRenderer output -> Both SourceBlob -> Task (Maybe output)
|
||||||
parseDiffAndRenderBlobPair renderer blobs = case renderer of
|
diffBlobPair renderer blobs = case renderer of
|
||||||
ToCDiffRenderer -> do
|
ToCDiffRenderer -> do
|
||||||
terms <- distributeFor blobs $ \ blob -> do
|
terms <- distributeFor blobs $ \ blob -> do
|
||||||
term <- parseSource blob
|
term <- parseSource blob
|
||||||
|
@ -21,7 +21,7 @@ import System.FilePath.Posix (takeFileName, (-<.>))
|
|||||||
import System.IO.Error (IOError)
|
import System.IO.Error (IOError)
|
||||||
import System.IO (stdin)
|
import System.IO (stdin)
|
||||||
import Text.Regex
|
import Text.Regex
|
||||||
import qualified Semantic (parseBlob, parseDiffAndRenderBlobPair)
|
import qualified Semantic (parseBlob, diffBlobPair)
|
||||||
|
|
||||||
main :: IO ()
|
main :: IO ()
|
||||||
main = do
|
main = do
|
||||||
@ -54,7 +54,7 @@ runDiff DiffArguments{..} = do
|
|||||||
DiffPaths a b -> pure <$> traverse (uncurry readFile) (both a b)
|
DiffPaths a b -> pure <$> traverse (uncurry readFile) (both a b)
|
||||||
DiffCommits sha1 sha2 paths -> readFilesAtSHAs gitDir alternateObjectDirs paths (both sha1 sha2)
|
DiffCommits sha1 sha2 paths -> readFilesAtSHAs gitDir alternateObjectDirs paths (both sha1 sha2)
|
||||||
DiffStdin -> readBlobPairsFromHandle stdin
|
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 -> IO ByteString
|
||||||
runParse ParseArguments{..} = do
|
runParse ParseArguments{..} = do
|
||||||
|
@ -138,4 +138,4 @@ data Fixture = Fixture { shas :: Both String, expectedBlobs :: [Both SourceBlob]
|
|||||||
fetchDiffsOutput :: FilePath -> String -> String -> [(FilePath, Maybe Language)] -> IO Summaries
|
fetchDiffsOutput :: FilePath -> String -> String -> [(FilePath, Maybe Language)] -> IO Summaries
|
||||||
fetchDiffsOutput gitDir sha1 sha2 filePaths = do
|
fetchDiffsOutput gitDir sha1 sha2 filePaths = do
|
||||||
blobPairs <- runCommand $ readFilesAtSHAs gitDir [] filePaths (both sha1 sha2)
|
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)
|
||||||
|
@ -27,7 +27,7 @@ import Term
|
|||||||
diffFilePaths :: Both FilePath -> IO ByteString
|
diffFilePaths :: Both FilePath -> IO ByteString
|
||||||
diffFilePaths paths = do
|
diffFilePaths paths = do
|
||||||
blobs <- traverse readFile paths
|
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.
|
-- | Returns an s-expression parse tree for the specified FilePath.
|
||||||
parseFilePath :: FilePath -> IO ByteString
|
parseFilePath :: FilePath -> IO ByteString
|
||||||
|
@ -58,7 +58,7 @@ spec = parallel $ do
|
|||||||
|
|
||||||
it "summarizes changed methods" $ do
|
it "summarizes changed methods" $ do
|
||||||
sourceBlobs <- blobsForPaths (both "ruby/methods.A.rb" "ruby/methods.B.rb")
|
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`
|
diffTOC diff `shouldBe`
|
||||||
[ JSONSummary $ Summarizable C.SingletonMethod "self.foo" (sourceSpanBetween (1, 1) (2, 4)) "added"
|
[ JSONSummary $ Summarizable C.SingletonMethod "self.foo" (sourceSpanBetween (1, 1) (2, 4)) "added"
|
||||||
, JSONSummary $ Summarizable C.Method "bar" (sourceSpanBetween (4, 1) (6, 4)) "modified"
|
, 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
|
it "dedupes changes in same parent method" $ do
|
||||||
sourceBlobs <- blobsForPaths (both "javascript/duplicate-parent.A.js" "javascript/duplicate-parent.B.js")
|
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`
|
diffTOC diff `shouldBe`
|
||||||
[ JSONSummary $ Summarizable C.Function "myFunction" (sourceSpanBetween (1, 1) (6, 2)) "modified" ]
|
[ JSONSummary $ Summarizable C.Function "myFunction" (sourceSpanBetween (1, 1) (6, 2)) "modified" ]
|
||||||
|
|
||||||
it "dedupes similar methods" $ do
|
it "dedupes similar methods" $ do
|
||||||
sourceBlobs <- blobsForPaths (both "javascript/erroneous-duplicate-method.A.js" "javascript/erroneous-duplicate-method.B.js")
|
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`
|
diffTOC diff `shouldBe`
|
||||||
[ JSONSummary $ Summarizable C.Function "performHealthCheck" (sourceSpanBetween (8, 1) (29, 2)) "modified" ]
|
[ JSONSummary $ Summarizable C.Function "performHealthCheck" (sourceSpanBetween (8, 1) (29, 2)) "modified" ]
|
||||||
|
|
||||||
it "summarizes Go methods with receivers with special formatting" $ do
|
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")
|
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`
|
diffTOC diff `shouldBe`
|
||||||
[ JSONSummary $ Summarizable C.Method "(*apiClient) CheckAuth" (sourceSpanBetween (3,1) (3,101)) "added" ]
|
[ JSONSummary $ Summarizable C.Method "(*apiClient) CheckAuth" (sourceSpanBetween (3,1) (3,101)) "added" ]
|
||||||
|
|
||||||
it "summarizes Ruby methods that start with two identifiers" $ do
|
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")
|
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`
|
diffTOC diff `shouldBe`
|
||||||
[ JSONSummary $ Summarizable C.Method "foo" (sourceSpanBetween (1, 1) (4, 4)) "modified" ]
|
[ JSONSummary $ Summarizable C.Method "foo" (sourceSpanBetween (1, 1) (4, 4)) "modified" ]
|
||||||
|
|
||||||
it "handles unicode characters in file" $ do
|
it "handles unicode characters in file" $ do
|
||||||
sourceBlobs <- blobsForPaths (both "ruby/unicode.A.rb" "ruby/unicode.B.rb")
|
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`
|
diffTOC diff `shouldBe`
|
||||||
[ JSONSummary $ Summarizable C.Method "foo" (sourceSpanBetween (6, 1) (7, 4)) "added" ]
|
[ JSONSummary $ Summarizable C.Method "foo" (sourceSpanBetween (6, 1) (7, 4)) "added" ]
|
||||||
|
|
||||||
@ -135,12 +135,12 @@ spec = parallel $ do
|
|||||||
describe "diff with ToCDiffRenderer" $ do
|
describe "diff with ToCDiffRenderer" $ do
|
||||||
it "produces JSON output" $ do
|
it "produces JSON output" $ do
|
||||||
blobs <- blobsForPaths (both "ruby/methods.A.rb" "ruby/methods.B.rb")
|
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)
|
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
|
it "produces JSON output if there are parse errors" $ do
|
||||||
blobs <- blobsForPaths (both "ruby/methods.A.rb" "ruby/methods.X.rb")
|
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)
|
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)
|
type Diff' = SyntaxDiff Text (Maybe Declaration ': DefaultFields)
|
||||||
|
Loading…
Reference in New Issue
Block a user