diff --git a/semantic-diff.cabal b/semantic-diff.cabal index 2c6918fac..46026583a 100644 --- a/semantic-diff.cabal +++ b/semantic-diff.cabal @@ -158,6 +158,7 @@ test-suite test , array , base , bifunctors + , bytestring , deepseq , filepath , gitlib diff --git a/test/DiffCommandSpec.hs b/test/DiffCommandSpec.hs index 0b95b6db9..cdc47799d 100644 --- a/test/DiffCommandSpec.hs +++ b/test/DiffCommandSpec.hs @@ -9,8 +9,8 @@ import Prologue (($), fmap, (.), pure, for, panic) import Test.Hspec hiding (shouldBe, shouldNotBe, shouldThrow, errorCall) import Test.Hspec.Expectations.Pretty import Test.Hspec.LeanCheck -import Data.Text.Lazy.Encoding as E import Data.Text.Lazy as T +import qualified Data.ByteString.Lazy as BL import Data.Map import qualified Data.Vector as V import Arguments @@ -58,7 +58,7 @@ spec = parallel $ do fetchDiffsOutput :: (Object -> Text) -> Arguments -> IO (Maybe (Map Text Value), Maybe (Map Text [Text])) fetchDiffsOutput f arguments = do diffs <- fetchDiffs arguments - let json = fromJust . decode . E.encodeUtf8 $ T.fromChunks [concatOutputs diffs] + let json = fromJust . decode . BL.fromStrict $ concatOutputs diffs pure (errors json, summaries f json) -- Diff Summaries payloads look like this: diff --git a/test/IntegrationSpec.hs b/test/IntegrationSpec.hs index c9fb427aa..a2c52b957 100644 --- a/test/IntegrationSpec.hs +++ b/test/IntegrationSpec.hs @@ -1,10 +1,12 @@ -{-# LANGUAGE DataKinds, GeneralizedNewtypeDeriving #-} +{-# LANGUAGE DataKinds, GeneralizedNewtypeDeriving, OverloadedStrings #-} module IntegrationSpec where import Category as C import Data.Functor.Both import Data.Record import qualified Data.Text as T +import qualified Data.ByteString as B +import Data.Text.Encoding (decodeUtf8) import GHC.Show (Show(..)) import Data.List (union, concat, transpose) import Info @@ -109,7 +111,7 @@ testParse path expectedOutput = do let blob = sourceBlob source path term <- parserWithSource path blob let actual = (Verbatim . stripWhitespace) $ printTerm term 0 TreeOnly - expected <- (Verbatim . stripWhitespace) <$> readFile expectedOutput + expected <- (Verbatim . stripWhitespace) <$> B.readFile expectedOutput actual `shouldBe` expected testDiff :: Renderer (Record '[Range, Category, SourceSpan]) -> Both FilePath -> FilePath -> Expectation @@ -117,7 +119,7 @@ testDiff renderer paths diff = do sources <- traverse readAndTranscodeFile' paths diff' <- diffFiles parser renderer (sourceBlobs sources) let actual = (Verbatim . stripWhitespace. concatOutputs . pure) diff' - expected <- (Verbatim . stripWhitespace) <$> readFile diff + expected <- (Verbatim . stripWhitespace) <$> B.readFile diff actual `shouldBe` expected where parser = parserForFilepath filePath @@ -126,14 +128,14 @@ testDiff renderer paths diff = do | otherwise = readAndTranscodeFile path filePath = if fst paths /= "" then fst paths else snd paths -stripWhitespace :: Text -> Text -stripWhitespace = T.foldl' go T.empty - where go acc x | x `elem` [' ', '\t', '\n'] = acc - | otherwise = T.snoc acc x +stripWhitespace :: ByteString -> ByteString +stripWhitespace = B.foldl' go B.empty + where go acc x | x `B.elem` " \t\n" = acc + | otherwise = B.snoc acc x --- | A wrapper around `Text` with a more readable `Show` instance. -newtype Verbatim = Verbatim Text +-- | A wrapper around `ByteString` with a more readable `Show` instance. +newtype Verbatim = Verbatim ByteString deriving (Eq, NFData) instance Show Verbatim where - showsPrec _ (Verbatim text) = ('\n':) . (T.unpack text ++) + showsPrec _ (Verbatim byteString) = ('\n':) . (T.unpack (decodeUtf8 byteString) ++) diff --git a/test/TOCSpec.hs b/test/TOCSpec.hs index 5db9365de..9a298e77c 100644 --- a/test/TOCSpec.hs +++ b/test/TOCSpec.hs @@ -112,13 +112,13 @@ spec = parallel $ 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) + 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\":{}}" ) 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) + 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\"}]}}" ) type Diff' = SyntaxDiff String '[Range, Category, SourceSpan] type Term' = SyntaxTerm String '[Range, Category, SourceSpan]