From 0cf38c583c3844e987d8f48c6dc063a7609b6710 Mon Sep 17 00:00:00 2001 From: Timothy Clem Date: Wed, 22 Feb 2017 20:05:20 -0800 Subject: [PATCH] Assert to summary json output --- semantic-diff.cabal | 3 ++- src/Renderer/TOC.hs | 2 +- test/TOCSpec.hs | 26 +++++++++++++++++++++++++- 3 files changed, 28 insertions(+), 3 deletions(-) diff --git a/semantic-diff.cabal b/semantic-diff.cabal index d6dbe8e89..6d3906a37 100644 --- a/semantic-diff.cabal +++ b/semantic-diff.cabal @@ -152,7 +152,8 @@ test-suite test , TOCSpec , IntegrationSpec , Test.Hspec.LeanCheck - build-depends: array + build-depends: aeson + , array , base , bifunctors , deepseq diff --git a/src/Renderer/TOC.hs b/src/Renderer/TOC.hs index e8319caf2..f5692d502 100644 --- a/src/Renderer/TOC.hs +++ b/src/Renderer/TOC.hs @@ -184,5 +184,5 @@ toTermName parentOffset parentSource term = case unwrap term of -- The user-facing category name toCategoryName :: Category -> Text toCategoryName = \case - C.SingletonMethod -> "method" + C.SingletonMethod -> "Method" c -> show c diff --git a/test/TOCSpec.hs b/test/TOCSpec.hs index 8e8ef21fd..9e14dfd96 100644 --- a/test/TOCSpec.hs +++ b/test/TOCSpec.hs @@ -1,6 +1,7 @@ {-# LANGUAGE DataKinds #-} module TOCSpec where +import Data.Aeson import Category as C import Data.Functor.Both import Data.Functor.Listable @@ -14,6 +15,7 @@ import Interpreter import Parse import Patch import Prologue hiding (fst, snd) +import Renderer import Renderer.TOC import Source import Syntax as S @@ -25,7 +27,7 @@ import Test.LeanCheck spec :: Spec spec = parallel $ do - describe "tocSummaries" $ do + describe "diffTOC" $ do it "blank if there are no methods" $ diffTOC blankDiffBlobs blankDiff `shouldBe` [ ] @@ -96,6 +98,28 @@ spec = parallel $ do \a -> let term = defaultFeatureVectorDecorator (Info.category . headF) (unListableF a :: Term') in diffTOC blankDiffBlobs (diffTerms term term) `shouldBe` [] + describe "JSONSummary" $ do + it "encodes InSummarizable to JSON" $ do + let summary = JSONSummary $ InSummarizable C.Method "foo" (sourceSpanBetween (1, 1) (4, 4)) + encode summary `shouldBe` "{\"span\":{\"start\":[1,1],\"end\":[4,4]},\"category\":\"Method\",\"term\":\"foo\",\"changeType\":\"modified\"}" + + it "encodes Summarizable to JSON" $ do + let summary = JSONSummary $ Summarizable C.SingletonMethod "self.foo" (sourceSpanBetween (1, 1) (2, 4)) "added" + encode summary `shouldBe` "{\"span\":{\"start\":[1,1],\"end\":[2,4]},\"category\":\"Method\",\"term\":\"self.foo\",\"changeType\":\"added\"}" + + describe "diffFiles" $ do + it "encodes to final JSON" $ do + sourceBlobs <- blobsForPaths (both "ruby/methods.A.rb" "ruby/methods.B.rb") + let parser = parserForFilepath (path (fst sourceBlobs)) + output <- diffFiles parser toc sourceBlobs + concatOutputs (pure output) `shouldBe` ("{\"changes\":{\"ruby/methods.A.rb -> 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\":{}}" :: Text) + + it "encodes to final JSON if there are parse errors" $ do + sourceBlobs <- blobsForPaths (both "ruby/methods.A.rb" "ruby/methods.X.rb") + let parser = parserForFilepath (path (fst sourceBlobs)) + output <- diffFiles parser toc sourceBlobs + concatOutputs (pure output) `shouldBe` ("{\"changes\":{},\"errors\":{\"ruby/methods.A.rb -> ruby/methods.X.rb\":[{\"span\":{\"start\":[1,1],\"end\":[3,1]},\"error\":\"def bar\\nen\\n\"}]}}" :: Text) + type Diff' = SyntaxDiff String '[Range, Category, SourceSpan] type Term' = SyntaxTerm String '[Range, Category, SourceSpan]