1
1
mirror of https://github.com/github/semantic.git synced 2025-01-02 04:10:29 +03:00

Merge branch 'master' into cli-refactoring

This commit is contained in:
Rob Rix 2017-07-19 19:55:03 -04:00 committed by GitHub
commit ebe21c348c
2 changed files with 35 additions and 29 deletions

View File

@ -33,6 +33,7 @@ import Data.These
import Data.Union
import Diff
import Info
import Language
import Patch
import Prologue
import qualified Data.List as List
@ -64,12 +65,12 @@ data JSONSummary
, summarySpan :: Span
, summaryChangeType :: Text
}
| ErrorSummary { error :: Text, errorSpan :: Span }
| ErrorSummary { error :: Text, errorSpan :: Span, errorLanguage :: Maybe Language }
deriving (Generic, Eq, Show)
instance ToJSON JSONSummary where
toJSON JSONSummary{..} = object [ "changeType" .= summaryChangeType, "category" .= summaryCategoryName, "term" .= summaryTermName, "span" .= summarySpan ]
toJSON ErrorSummary{..} = object [ "error" .= error, "span" .= errorSpan ]
toJSON ErrorSummary{..} = object [ "error" .= error, "span" .= errorSpan, "language" .= errorLanguage ]
isValidSummary :: JSONSummary -> Bool
isValidSummary ErrorSummary{} = False
@ -171,25 +172,30 @@ dedupe = foldl' go []
similarDeclaration = (==) `on` fmap (toLower . declarationIdentifier) . getDeclaration
-- | Construct a 'JSONSummary' from an 'Entry'. Returns 'Nothing' for 'Unchanged' patches.
entrySummary :: (HasField fields (Maybe Declaration), HasField fields Span) => Entry (Record fields) -> Maybe JSONSummary
entrySummary entry = case entry of
entrySummary :: (HasField fields (Maybe Declaration), HasField fields Span) => Maybe Language -> Entry (Record fields) -> Maybe JSONSummary
entrySummary language entry = case entry of
Unchanged _ -> Nothing
Changed a -> recordSummary a "modified"
Deleted a -> recordSummary a "removed"
Inserted a -> recordSummary a "added"
Replaced a -> recordSummary a "modified"
Changed a -> recordSummary language a "modified"
Deleted a -> recordSummary language a "removed"
Inserted a -> recordSummary language a "added"
Replaced a -> recordSummary language a "modified"
-- | Construct a 'JSONSummary' from a node annotation and a change type label.
recordSummary :: (HasField fields (Maybe Declaration), HasField fields Span) => Record fields -> Text -> Maybe JSONSummary
recordSummary record = case getDeclaration record of
Just (ErrorDeclaration text) -> Just . const (ErrorSummary text (sourceSpan record))
recordSummary :: (HasField fields (Maybe Declaration), HasField fields Span) => Maybe Language -> Record fields -> Text -> Maybe JSONSummary
recordSummary language record = case getDeclaration record of
Just (ErrorDeclaration text) -> Just . const (ErrorSummary text (sourceSpan record) language)
Just declaration -> Just . JSONSummary (toCategoryName declaration) (declarationIdentifier declaration) (sourceSpan record)
Nothing -> const Nothing
renderToCDiff :: (HasField fields (Maybe Declaration), HasField fields Span, Traversable f) => Both Blob -> Diff f (Record fields) -> Summaries
renderToCDiff blobs = uncurry Summaries . bimap toMap toMap . List.partition isValidSummary . diffTOC
renderToCDiff blobs = uncurry Summaries . bimap toMap toMap . List.partition isValidSummary . diffTOC language
where toMap [] = mempty
toMap as = Map.singleton summaryKey (toJSON <$> as)
language = case runJoin (blobLanguage <$> blobs) of
(Nothing, Just after) -> Just after
(Just before, Nothing) -> Just before
(Nothing, Nothing) -> Nothing
(Just before, Just _) -> Just before
summaryKey = toS $ case runJoin (blobPath <$> blobs) of
(before, after) | null before -> after
| null after -> before
@ -197,15 +203,15 @@ renderToCDiff blobs = uncurry Summaries . bimap toMap toMap . List.partition isV
| otherwise -> before <> " -> " <> after
renderToCTerm :: (HasField fields (Maybe Declaration), HasField fields Span, Traversable f) => Blob -> Term f (Record fields) -> Summaries
renderToCTerm blob = uncurry Summaries . bimap toMap toMap . List.partition isValidSummary . termToC
renderToCTerm Blob{..} = uncurry Summaries . bimap toMap toMap . List.partition isValidSummary . termToC blobLanguage
where toMap [] = mempty
toMap as = Map.singleton (toS (blobPath blob)) (toJSON <$> as)
toMap as = Map.singleton (toS blobPath) (toJSON <$> as)
diffTOC :: (HasField fields (Maybe Declaration), HasField fields Span, Traversable f) => Diff f (Record fields) -> [JSONSummary]
diffTOC = mapMaybe entrySummary . dedupe . tableOfContentsBy declaration
diffTOC :: (HasField fields (Maybe Declaration), HasField fields Span, Traversable f) => Maybe Language -> Diff f (Record fields) -> [JSONSummary]
diffTOC language = mapMaybe (entrySummary language) . dedupe . tableOfContentsBy declaration
termToC :: (HasField fields (Maybe Declaration), HasField fields Span, Traversable f) => Term f (Record fields) -> [JSONSummary]
termToC = mapMaybe (flip recordSummary "unchanged") . termTableOfContentsBy declaration
termToC :: (HasField fields (Maybe Declaration), HasField fields Span, Traversable f) => Maybe Language -> Term f (Record fields) -> [JSONSummary]
termToC language = mapMaybe (flip (recordSummary language) "unchanged") . termTableOfContentsBy declaration
-- The user-facing category name
toCategoryName :: Declaration -> Text

View File

@ -55,12 +55,12 @@ spec = parallel $ do
describe "diffTOC" $ do
it "blank if there are no methods" $
diffTOC blankDiff `shouldBe` [ ]
diffTOC Nothing blankDiff `shouldBe` [ ]
it "summarizes changed methods" $ do
sourceBlobs <- blobsForPaths (both "ruby/methods.A.rb" "ruby/methods.B.rb")
Just diff <- runTask (diffBlobPair IdentityDiffRenderer sourceBlobs)
diffTOC diff `shouldBe`
diffTOC (Just Ruby) diff `shouldBe`
[ JSONSummary "Method" "self.foo" (sourceSpanBetween (1, 1) (2, 4)) "added"
, JSONSummary "Method" "bar" (sourceSpanBetween (4, 1) (6, 4)) "modified"
, JSONSummary "Method" "baz" (sourceSpanBetween (4, 1) (5, 4)) "removed" ]
@ -68,37 +68,37 @@ 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 (diffBlobPair IdentityDiffRenderer sourceBlobs)
diffTOC diff `shouldBe`
diffTOC Nothing diff `shouldBe`
[ JSONSummary "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 (diffBlobPair IdentityDiffRenderer sourceBlobs)
diffTOC diff `shouldBe`
diffTOC (Just JavaScript) diff `shouldBe`
[ JSONSummary "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 (diffBlobPair IdentityDiffRenderer sourceBlobs)
diffTOC diff `shouldBe`
diffTOC (Just Language.Go) diff `shouldBe`
[ JSONSummary "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 (diffBlobPair IdentityDiffRenderer sourceBlobs)
diffTOC diff `shouldBe`
diffTOC (Just Ruby) diff `shouldBe`
[ JSONSummary "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 (diffBlobPair IdentityDiffRenderer sourceBlobs)
diffTOC diff `shouldBe`
diffTOC (Just Ruby) diff `shouldBe`
[ JSONSummary "Method" "foo" (sourceSpanBetween (6, 1) (7, 4)) "added" ]
it "properly slices source blob that starts with a newline and has multi-byte chars" $ do
sourceBlobs <- blobsForPaths (both "javascript/starts-with-newline.js" "javascript/starts-with-newline.js")
Just diff <- runTask (diffBlobPair IdentityDiffRenderer sourceBlobs)
diffTOC diff `shouldBe` []
diffTOC (Just JavaScript) diff `shouldBe` []
prop "inserts of methods and functions are summarized" $
\name body ->
@ -127,7 +127,7 @@ spec = parallel $ do
prop "equal terms produce identity diffs" $
\a -> let term = defaultFeatureVectorDecorator (Info.category . headF) (unListableF a :: Term') in
diffTOC (diffTerms (pure term)) `shouldBe` []
diffTOC Nothing (diffTerms (pure term)) `shouldBe` []
describe "JSONSummary" $ do
it "encodes modified summaries to JSON" $ do
@ -147,7 +147,7 @@ spec = parallel $ do
it "produces JSON output if there are parse errors" $ do
blobs <- blobsForPaths (both "ruby/methods.A.rb" "ruby/methods.X.rb")
output <- runTask (diffBlobPair ToCDiffRenderer blobs)
toS output `shouldBe` ("{\"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)
toS output `shouldBe` ("{\"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\",\"language\":\"Ruby\"}]}}\n" :: ByteString)
it "summarizes Markdown headings" $ do
blobs <- blobsForPaths (both "markdown/headings.A.md" "markdown/headings.B.md")
@ -159,7 +159,7 @@ type Diff' = SyntaxDiff Text (Maybe Declaration ': DefaultFields)
type Term' = SyntaxTerm Text (Maybe Declaration ': DefaultFields)
numTocSummaries :: Diff' -> Int
numTocSummaries diff = length $ filter isValidSummary (diffTOC diff)
numTocSummaries diff = length $ filter isValidSummary (diffTOC Nothing diff)
-- 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'