mirror of
https://github.com/github/semantic.git
synced 2024-11-28 10:15:55 +03:00
Merge remote-tracking branch 'origin/master' into one-json-to-rule-them-all
This commit is contained in:
commit
59932277f9
@ -129,6 +129,7 @@ test-suite semantic-diff-test
|
||||
, free
|
||||
, recursion-schemes >= 4.1
|
||||
, wl-pprint-text
|
||||
, protolude
|
||||
if os(darwin)
|
||||
ghc-options: -threaded -rtsopts -with-rtsopts=-N -j
|
||||
else
|
||||
|
@ -83,7 +83,7 @@ showLine source line | Just line <- line = Just . toString . (`slice` source) $
|
||||
|
||||
-- | Returns the header given two source blobs and a hunk.
|
||||
header :: Both SourceBlob -> String
|
||||
header blobs = intercalate "\n" [filepathHeader, fileModeHeader, beforeFilepath, afterFilepath] <> "\n"
|
||||
header blobs = intercalate "\n" ([filepathHeader, fileModeHeader] <> maybeFilepaths) <> "\n"
|
||||
where filepathHeader = "diff --git a/" <> pathA <> " b/" <> pathB
|
||||
fileModeHeader = case (modeA, modeB) of
|
||||
(Nothing, Just mode) -> intercalate "\n" [ "new file mode " <> modeToDigits mode, blobOidHeader ]
|
||||
@ -100,9 +100,14 @@ header blobs = intercalate "\n" [filepathHeader, fileModeHeader, beforeFilepath,
|
||||
modeHeader ty maybeMode path = case maybeMode of
|
||||
Just _ -> ty <> "/" <> path
|
||||
Nothing -> "/dev/null"
|
||||
maybeFilepaths = if (nullOid == oidA && null (snd sources)) || (nullOid == oidB && null (fst sources)) then [] else [ beforeFilepath, afterFilepath ]
|
||||
beforeFilepath = "--- " <> modeHeader "a" modeA pathA
|
||||
afterFilepath = "+++ " <> modeHeader "b" modeB pathB
|
||||
(pathA, pathB) = runJoin $ path <$> blobs
|
||||
sources = source <$> blobs
|
||||
(pathA, pathB) = case runJoin $ path <$> blobs of
|
||||
("", path) -> (path, path)
|
||||
(path, "") -> (path, path)
|
||||
paths -> paths
|
||||
(oidA, oidB) = runJoin $ oid <$> blobs
|
||||
(modeA, modeB) = runJoin $ blobKind <$> blobs
|
||||
|
||||
|
@ -30,6 +30,11 @@ modeToDigits (SymlinkBlob mode) = showOct mode ""
|
||||
defaultPlainBlob :: SourceKind
|
||||
defaultPlainBlob = PlainBlob 0o100644
|
||||
|
||||
emptySourceBlob :: FilePath -> SourceBlob
|
||||
emptySourceBlob filepath = SourceBlob (Source.fromList "") Source.nullOid filepath Nothing
|
||||
|
||||
sourceBlob :: Source Char -> FilePath -> SourceBlob
|
||||
sourceBlob source filepath = SourceBlob source Source.nullOid filepath (Just defaultPlainBlob)
|
||||
|
||||
-- | Map blobs with Nothing blobKind to empty blobs.
|
||||
idOrEmptySourceBlob :: SourceBlob -> SourceBlob
|
||||
|
@ -1,6 +1,7 @@
|
||||
{-# LANGUAGE DataKinds, FlexibleContexts, GeneralizedNewtypeDeriving #-}
|
||||
module CorpusSpec where
|
||||
|
||||
import Unsafe (unsafeFromJust)
|
||||
import Diffing
|
||||
import Renderer
|
||||
import qualified Renderer.JSON as J
|
||||
@ -10,13 +11,11 @@ import qualified Renderer.Split as Split
|
||||
import Category
|
||||
import Control.DeepSeq
|
||||
import Data.Functor.Both
|
||||
import Data.List as List
|
||||
import Data.Map as Map
|
||||
import Data.Record
|
||||
import Data.Set as Set
|
||||
import Data.List (union)
|
||||
import qualified Data.Text as T
|
||||
import Info
|
||||
import Prologue hiding (fst, snd)
|
||||
import Prologue hiding (fst, snd, lookup)
|
||||
import qualified Source as S
|
||||
import System.FilePath
|
||||
import System.FilePath.Glob
|
||||
@ -25,7 +24,8 @@ import GHC.Show (Show(..))
|
||||
|
||||
spec :: Spec
|
||||
spec = parallel $ do
|
||||
describe "crashers crash" $ runTestsIn "test/crashers-todo/" $ \ a b -> a `deepseq` pure (a == b) `shouldThrow` anyException
|
||||
describe "crashers crash" $ runTestsIn "test/crashers-todo/" (\ a b ->
|
||||
a `deepseq` pure (a == b) `shouldThrow` anyException)
|
||||
describe "crashers should not crash" $ runTestsIn "test/crashers/" shouldBe
|
||||
describe "todos are incorrect" $ runTestsIn "test/diffs-todo/" shouldNotBe
|
||||
describe "should produce the correct diff" $ runTestsIn "test/diffs/" shouldBe
|
||||
@ -35,32 +35,36 @@ spec = parallel $ do
|
||||
examples "test/diffs/" `shouldNotReturn` []
|
||||
|
||||
where
|
||||
runTestsIn :: FilePath -> (Verbatim -> Verbatim -> Expectation) -> SpecWith ()
|
||||
runTestsIn :: FilePath -> (Maybe Verbatim -> Maybe Verbatim -> Expectation) -> SpecWith ()
|
||||
runTestsIn directory matcher = do
|
||||
paths <- runIO $ examples directory
|
||||
let tests = correctTests =<< paths
|
||||
traverse_ (\ (formatName, renderer, paths, output) -> it (normalizeName (fst paths) ++ " (" ++ formatName ++ ")") $ testDiff renderer paths output matcher) tests
|
||||
|
||||
correctTests paths@(_, Nothing, Nothing, Nothing) = testsForPaths paths
|
||||
correctTests paths = List.filter (\(_, _, _, output) -> isJust output) $ testsForPaths paths
|
||||
testsForPaths (paths, json, patch, split) = [ ("json", J.json, paths, json), ("patch", P.patch, paths, patch), ("split", Split.split, paths, split) ]
|
||||
traverse_ (\ (formatName, renderer, paths, output) ->
|
||||
it (maybe "/dev/null" normalizeName (uncurry (<|>) (runJoin paths)) ++ " (" ++ formatName ++ ")") $ testDiff renderer paths output matcher) tests
|
||||
|
||||
correctTests paths@(_, _, Nothing, Nothing, Nothing) = testsForPaths paths
|
||||
correctTests paths = filter (\(_, _, _, output) -> isJust output) $ testsForPaths paths
|
||||
testsForPaths (aPath, bPath, json, patch, split) = [ ("json", J.json, paths, json), ("patch", P.patch, paths, patch), ("split", Split.split, paths, split) ]
|
||||
where paths = both aPath bPath
|
||||
-- | Return all the examples from the given directory. Examples are expected to
|
||||
-- | have the form "foo.A.js", "foo.B.js", "foo.patch.js". Diffs are not
|
||||
-- | required as the test may be verifying that the inputs don't crash.
|
||||
examples :: FilePath -> IO [(Both FilePath, Maybe FilePath, Maybe FilePath, Maybe FilePath)]
|
||||
examples :: FilePath -> IO [(Maybe FilePath, Maybe FilePath, Maybe FilePath, Maybe FilePath, Maybe FilePath)]
|
||||
examples directory = do
|
||||
as <- toDict <$> globFor "*.A.*"
|
||||
bs <- toDict <$> globFor "*.B.*"
|
||||
jsons <- toDict <$> globFor "*.json.*"
|
||||
patches <- toDict <$> globFor "*.patch.*"
|
||||
splits <- toDict <$> globFor "*.split.*"
|
||||
let keys = Set.unions $ keysSet <$> [as, bs]
|
||||
pure $ (\name -> (both (as ! name) (bs ! name), Map.lookup name jsons, Map.lookup name patches, Map.lookup name splits)) <$> sort (Set.toList keys)
|
||||
as <- globFor "*.A.*"
|
||||
bs <- globFor "*.B.*"
|
||||
jsons <- globFor "*.json.*"
|
||||
patches <- globFor "*.patch.*"
|
||||
splits <- globFor "*.split.*"
|
||||
|
||||
let lookupName name = (lookupNormalized name as, lookupNormalized name bs, lookupNormalized name jsons, lookupNormalized name patches, lookupNormalized name splits)
|
||||
|
||||
let keys = (normalizeName <$> as) `union` (normalizeName <$> bs)
|
||||
pure $ lookupName <$> keys
|
||||
where
|
||||
lookupNormalized name = find $ (== name) . normalizeName
|
||||
globFor :: FilePath -> IO [FilePath]
|
||||
globFor p = globDir1 (compile p) directory
|
||||
toDict list = Map.fromList ((normalizeName <$> list) `zip` list)
|
||||
|
||||
-- | Given a test name like "foo.A.js", return "foo.js".
|
||||
normalizeName :: FilePath -> FilePath
|
||||
@ -69,17 +73,23 @@ normalizeName path = addExtension (dropExtension $ dropExtension path) (takeExte
|
||||
-- | Given file paths for A, B, and, optionally, a diff, return whether diffing
|
||||
-- | the files will produce the diff. If no diff is provided, then the result
|
||||
-- | is true, but the diff will still be calculated.
|
||||
testDiff :: Renderer (Record '[Range, Category, Cost]) -> Both FilePath -> Maybe FilePath -> (Verbatim -> Verbatim -> Expectation) -> Expectation
|
||||
testDiff :: Renderer (Record '[Range, Category, Cost]) -> Both (Maybe FilePath) -> Maybe FilePath -> (Maybe Verbatim -> Maybe Verbatim -> Expectation) -> Expectation
|
||||
testDiff renderer paths diff matcher = do
|
||||
sources <- sequence $ readAndTranscodeFile <$> paths
|
||||
actual <- Verbatim <$> (pure . concatOutputs . (:[]) =<< diffFiles parser renderer (sourceBlobs sources))
|
||||
sources <- traverse (traverse readAndTranscodeFile) paths
|
||||
actual <- fmap Verbatim <$> traverse ((pure . concatOutputs . pure) <=< diffFiles' sources) parser
|
||||
case diff of
|
||||
Nothing -> matcher actual actual
|
||||
Just file -> do
|
||||
expected <- Verbatim <$> readFile file
|
||||
matcher actual expected
|
||||
where parser = parserForFilepath (fst paths)
|
||||
sourceBlobs sources = pure S.SourceBlob <*> sources <*> pure mempty <*> paths <*> pure (Just S.defaultPlainBlob)
|
||||
matcher actual (Just expected)
|
||||
where diffFiles' sources parser = diffFiles parser renderer (sourceBlobs sources paths)
|
||||
parser = parserForFilepath <$> runBothWith (<|>) paths
|
||||
sourceBlobs :: Both (Maybe (S.Source Char)) -> Both (Maybe FilePath) -> Both S.SourceBlob
|
||||
sourceBlobs sources paths = case runJoin paths of
|
||||
(Nothing, Nothing) -> Join (S.emptySourceBlob "", S.emptySourceBlob "")
|
||||
(Nothing, Just filepath) -> Join (S.emptySourceBlob "", S.sourceBlob (unsafeFromJust $ snd sources) filepath)
|
||||
(Just filepath, Nothing) -> Join (S.sourceBlob (unsafeFromJust $ fst sources) filepath, S.emptySourceBlob "")
|
||||
(Just path1, Just path2) -> Join (S.sourceBlob (unsafeFromJust $ fst sources) path1, S.sourceBlob (unsafeFromJust $ snd sources) path2)
|
||||
|
||||
-- | A wrapper around `Text` with a more readable `Show` instance.
|
||||
newtype Verbatim = Verbatim Text
|
||||
|
@ -1 +1 @@
|
||||
{"rows":[[{"number":1,"terms":[{"range":[0,2],"category":"Program","children":[{"range":[0,2],"category":"ExpressionStatements","children":[{"range":[0,2],"category":"Object","children":[]}]}]}],"range":[0,2],"hasChanges":false},{"number":1,"terms":[{"range":[0,2],"category":"Program","children":[{"range":[0,2],"category":"ExpressionStatements","children":[{"range":[0,2],"category":"Object","children":[]}]}]}],"range":[0,2],"hasChanges":false}],[{"number":2,"terms":[{"range":[2,12],"category":"Program","children":[{"range":[2,12],"category":"ExpressionStatements","children":[{"range":[2,12],"category":"Object","children":[{"range":[4,10],"category":"Pair","children":[{"range":[4,7],"category":"StringLiteral","children":[{"range":[4,5],"category":"StringLiteral"},{"range":[5,6],"category":"StringLiteral"},{"range":[6,7],"category":"StringLiteral"}]},{"patch":"replace","range":[9,10],"category":"number"}]}]}]}]}],"range":[2,12],"hasChanges":true},{"number":2,"terms":[{"range":[2,12],"category":"Program","children":[{"range":[2,12],"category":"ExpressionStatements","children":[{"range":[2,12],"category":"Object","children":[{"range":[4,10],"category":"Pair","children":[{"range":[4,7],"category":"StringLiteral","children":[{"range":[4,5],"category":"StringLiteral"},{"range":[5,6],"category":"StringLiteral"},{"range":[6,7],"category":"StringLiteral"}]},{"patch":"replace","range":[9,10],"category":"number"}]}]}]}]}],"range":[2,12],"hasChanges":true}],[{"number":3,"terms":[{"range":[12,21],"category":"Program","children":[{"range":[12,21],"category":"ExpressionStatements","children":[{"range":[12,21],"category":"Object","children":[{"range":[14,20],"category":"Pair","children":[{"range":[14,17],"category":"StringLiteral","children":[{"range":[14,15],"category":"StringLiteral"},{"range":[15,16],"category":"StringLiteral"},{"range":[16,17],"category":"StringLiteral"}]},{"range":[19,20],"category":"number"}]}]}]}]}],"range":[12,21],"hasChanges":false},{"number":3,"terms":[{"range":[12,21],"category":"Program","children":[{"range":[12,21],"category":"ExpressionStatements","children":[{"range":[12,21],"category":"Object","children":[{"range":[14,20],"category":"Pair","children":[{"range":[14,17],"category":"StringLiteral","children":[{"range":[14,15],"category":"StringLiteral"},{"range":[15,16],"category":"StringLiteral"},{"range":[16,17],"category":"StringLiteral"}]},{"range":[19,20],"category":"number"}]}]}]}]}],"range":[12,21],"hasChanges":false}],[{"number":4,"terms":[{"range":[21,23],"category":"Program","children":[{"range":[21,23],"category":"ExpressionStatements","children":[{"range":[21,22],"category":"Object","children":[]}]}]}],"range":[21,23],"hasChanges":false},{"number":4,"terms":[{"range":[21,23],"category":"Program","children":[{"range":[21,23],"category":"ExpressionStatements","children":[{"range":[21,22],"category":"Object","children":[]}]}]}],"range":[21,23],"hasChanges":false}],[{"number":5,"terms":[{"range":[23,23],"category":"Program","children":[]}],"range":[23,23],"hasChanges":false},{"number":5,"terms":[{"range":[23,23],"category":"Program","children":[]}],"range":[23,23],"hasChanges":false}]],"oids":["",""],"paths":["test/diffs/dictionary.A.js","test/diffs/dictionary.B.js"]}
|
||||
{"rows":[[{"number":1,"terms":[{"range":[0,2],"category":"Program","children":[{"range":[0,2],"category":"ExpressionStatements","children":[{"range":[0,2],"category":"Object","children":[]}]}]}],"range":[0,2],"hasChanges":false},{"number":1,"terms":[{"range":[0,2],"category":"Program","children":[{"range":[0,2],"category":"ExpressionStatements","children":[{"range":[0,2],"category":"Object","children":[]}]}]}],"range":[0,2],"hasChanges":false}],[{"number":2,"terms":[{"range":[2,12],"category":"Program","children":[{"range":[2,12],"category":"ExpressionStatements","children":[{"range":[2,12],"category":"Object","children":[{"range":[4,10],"category":"Pair","children":[{"range":[4,7],"category":"StringLiteral","children":[{"range":[4,5],"category":"StringLiteral"},{"range":[5,6],"category":"StringLiteral"},{"range":[6,7],"category":"StringLiteral"}]},{"patch":"replace","range":[9,10],"category":"number"}]}]}]}]}],"range":[2,12],"hasChanges":true},{"number":2,"terms":[{"range":[2,12],"category":"Program","children":[{"range":[2,12],"category":"ExpressionStatements","children":[{"range":[2,12],"category":"Object","children":[{"range":[4,10],"category":"Pair","children":[{"range":[4,7],"category":"StringLiteral","children":[{"range":[4,5],"category":"StringLiteral"},{"range":[5,6],"category":"StringLiteral"},{"range":[6,7],"category":"StringLiteral"}]},{"patch":"replace","range":[9,10],"category":"number"}]}]}]}]}],"range":[2,12],"hasChanges":true}],[{"number":3,"terms":[{"range":[12,21],"category":"Program","children":[{"range":[12,21],"category":"ExpressionStatements","children":[{"range":[12,21],"category":"Object","children":[{"range":[14,20],"category":"Pair","children":[{"range":[14,17],"category":"StringLiteral","children":[{"range":[14,15],"category":"StringLiteral"},{"range":[15,16],"category":"StringLiteral"},{"range":[16,17],"category":"StringLiteral"}]},{"range":[19,20],"category":"number"}]}]}]}]}],"range":[12,21],"hasChanges":false},{"number":3,"terms":[{"range":[12,21],"category":"Program","children":[{"range":[12,21],"category":"ExpressionStatements","children":[{"range":[12,21],"category":"Object","children":[{"range":[14,20],"category":"Pair","children":[{"range":[14,17],"category":"StringLiteral","children":[{"range":[14,15],"category":"StringLiteral"},{"range":[15,16],"category":"StringLiteral"},{"range":[16,17],"category":"StringLiteral"}]},{"range":[19,20],"category":"number"}]}]}]}]}],"range":[12,21],"hasChanges":false}],[{"number":4,"terms":[{"range":[21,23],"category":"Program","children":[{"range":[21,23],"category":"ExpressionStatements","children":[{"range":[21,22],"category":"Object","children":[]}]}]}],"range":[21,23],"hasChanges":false},{"number":4,"terms":[{"range":[21,23],"category":"Program","children":[{"range":[21,23],"category":"ExpressionStatements","children":[{"range":[21,22],"category":"Object","children":[]}]}]}],"range":[21,23],"hasChanges":false}],[{"number":5,"terms":[{"range":[23,23],"category":"Program","children":[]}],"range":[23,23],"hasChanges":false},{"number":5,"terms":[{"range":[23,23],"category":"Program","children":[]}],"range":[23,23],"hasChanges":false}]],"oids":["0000000000000000000000000000000000000000","0000000000000000000000000000000000000000"],"paths":["test/diffs/dictionary.A.js","test/diffs/dictionary.B.js"]}
|
0
test/diffs/file-addition.B.js
Normal file
0
test/diffs/file-addition.B.js
Normal file
3
test/diffs/file-addition.patch.js
Normal file
3
test/diffs/file-addition.patch.js
Normal file
@ -0,0 +1,3 @@
|
||||
diff --git a/test/diffs/file-addition.B.js b/test/diffs/file-addition.B.js
|
||||
new file mode 100644
|
||||
index 0000000000000000000000000000000000000000..0000000000000000000000000000000000000000
|
0
test/diffs/file-deletion.A.js
Normal file
0
test/diffs/file-deletion.A.js
Normal file
3
test/diffs/file-deletion.patch.js
Normal file
3
test/diffs/file-deletion.patch.js
Normal file
@ -0,0 +1,3 @@
|
||||
diff --git a/test/diffs/file-deletion.A.js b/test/diffs/file-deletion.A.js
|
||||
deleted file mode 100644
|
||||
index 0000000000000000000000000000000000000000..0000000000000000000000000000000000000000
|
@ -1,5 +1,5 @@
|
||||
diff --git a/test/diffs/jquery.A.js b/test/diffs/jquery.B.js
|
||||
index .. 100644
|
||||
index 0000000000000000000000000000000000000000..0000000000000000000000000000000000000000 100644
|
||||
--- a/test/diffs/jquery.A.js
|
||||
+++ b/test/diffs/jquery.B.js
|
||||
@@ -3,7 +3,7 @@
|
||||
|
@ -1,5 +1,5 @@
|
||||
diff --git a/test/diffs/multiple-hunks.A.js b/test/diffs/multiple-hunks.B.js
|
||||
index .. 100644
|
||||
index 0000000000000000000000000000000000000000..0000000000000000000000000000000000000000 100644
|
||||
--- a/test/diffs/multiple-hunks.A.js
|
||||
+++ b/test/diffs/multiple-hunks.B.js
|
||||
@@ -1,5 +1,5 @@
|
||||
|
@ -1 +1 @@
|
||||
{"rows":[[{"number":1,"terms":[{"range":[0,29],"category":"Program","children":[{"range":[0,28],"category":"ExpressionStatements","children":[{"range":[0,27],"category":"MethodCall","children":[{"range":[0,7],"category":"Identifier"},{"range":[8,11],"category":"Identifier"},{"range":[12,26],"category":"Args","children":[{"range":[12,26],"category":"StringLiteral","children":[{"range":[12,13],"category":"StringLiteral"},{"range":[13,18],"category":"StringLiteral"},{"range":[18,19],"category":"StringLiteral"},{"range":[20,25],"category":"StringLiteral"},{"range":[25,26],"category":"StringLiteral"}]}]}]}]}]}],"range":[0,29],"hasChanges":false},{"number":1,"terms":[{"range":[0,29],"category":"Program","children":[{"range":[0,28],"category":"ExpressionStatements","children":[{"range":[0,27],"category":"MethodCall","children":[{"range":[0,7],"category":"Identifier"},{"range":[8,11],"category":"Identifier"},{"range":[12,26],"category":"Args","children":[{"range":[12,26],"category":"StringLiteral","children":[{"range":[12,13],"category":"StringLiteral"},{"range":[13,18],"category":"StringLiteral"},{"range":[18,19],"category":"StringLiteral"},{"range":[20,25],"category":"StringLiteral"},{"range":[25,26],"category":"StringLiteral"}]}]}]}]}]}],"range":[0,29],"hasChanges":false}],[{"number":2,"terms":[{"range":[29,29],"category":"Program","children":[]}],"range":[29,29],"hasChanges":false},{"number":2,"terms":[{"range":[29,30],"category":"Program","children":[]}],"range":[29,30],"hasChanges":false}],[{"number":3,"terms":[{"range":[30,56],"category":"Program","children":[{"patch":"insert","range":[30,55],"category":"ExpressionStatements","children":[{"range":[30,54],"category":"MethodCall","children":[{"range":[30,37],"category":"Identifier"},{"range":[38,41],"category":"Identifier"},{"range":[42,53],"category":"Args","children":[{"range":[42,53],"category":"StringLiteral","children":[{"range":[42,43],"category":"StringLiteral"},{"range":[43,52],"category":"StringLiteral"},{"range":[52,53],"category":"StringLiteral"}]}]}]}]}]}],"range":[30,56],"hasChanges":true}],[{"number":4,"terms":[{"range":[56,56],"category":"Program","children":[]}],"range":[56,56],"hasChanges":false}]],"oids":["",""],"paths":["test/diffs/newline-at-eof.A.js","test/diffs/newline-at-eof.B.js"]}
|
||||
{"rows":[[{"number":1,"terms":[{"range":[0,29],"category":"Program","children":[{"range":[0,28],"category":"ExpressionStatements","children":[{"range":[0,27],"category":"MethodCall","children":[{"range":[0,7],"category":"Identifier"},{"range":[8,11],"category":"Identifier"},{"range":[12,26],"category":"Args","children":[{"range":[12,26],"category":"StringLiteral","children":[{"range":[12,13],"category":"StringLiteral"},{"range":[13,18],"category":"StringLiteral"},{"range":[18,19],"category":"StringLiteral"},{"range":[20,25],"category":"StringLiteral"},{"range":[25,26],"category":"StringLiteral"}]}]}]}]}]}],"range":[0,29],"hasChanges":false},{"number":1,"terms":[{"range":[0,29],"category":"Program","children":[{"range":[0,28],"category":"ExpressionStatements","children":[{"range":[0,27],"category":"MethodCall","children":[{"range":[0,7],"category":"Identifier"},{"range":[8,11],"category":"Identifier"},{"range":[12,26],"category":"Args","children":[{"range":[12,26],"category":"StringLiteral","children":[{"range":[12,13],"category":"StringLiteral"},{"range":[13,18],"category":"StringLiteral"},{"range":[18,19],"category":"StringLiteral"},{"range":[20,25],"category":"StringLiteral"},{"range":[25,26],"category":"StringLiteral"}]}]}]}]}]}],"range":[0,29],"hasChanges":false}],[{"number":2,"terms":[{"range":[29,29],"category":"Program","children":[]}],"range":[29,29],"hasChanges":false},{"number":2,"terms":[{"range":[29,30],"category":"Program","children":[]}],"range":[29,30],"hasChanges":false}],[{"number":3,"terms":[{"range":[30,56],"category":"Program","children":[{"patch":"insert","range":[30,55],"category":"ExpressionStatements","children":[{"range":[30,54],"category":"MethodCall","children":[{"range":[30,37],"category":"Identifier"},{"range":[38,41],"category":"Identifier"},{"range":[42,53],"category":"Args","children":[{"range":[42,53],"category":"StringLiteral","children":[{"range":[42,43],"category":"StringLiteral"},{"range":[43,52],"category":"StringLiteral"},{"range":[52,53],"category":"StringLiteral"}]}]}]}]}]}],"range":[30,56],"hasChanges":true}],[{"number":4,"terms":[{"range":[56,56],"category":"Program","children":[]}],"range":[56,56],"hasChanges":false}]],"oids":["0000000000000000000000000000000000000000","0000000000000000000000000000000000000000"],"paths":["test/diffs/newline-at-eof.A.js","test/diffs/newline-at-eof.B.js"]}
|
@ -1,5 +1,5 @@
|
||||
diff --git a/test/diffs/newline-at-eof.A.js b/test/diffs/newline-at-eof.B.js
|
||||
index .. 100644
|
||||
index 0000000000000000000000000000000000000000..0000000000000000000000000000000000000000 100644
|
||||
--- a/test/diffs/newline-at-eof.A.js
|
||||
+++ b/test/diffs/newline-at-eof.B.js
|
||||
@@ -1,2 +1,4 @@
|
||||
|
@ -1 +1 @@
|
||||
{"rows":[[{"number":1,"terms":[{"range":[0,28],"category":"Program","children":[{"range":[0,28],"category":"ExpressionStatements","children":[{"range":[0,27],"category":"MethodCall","children":[{"range":[0,7],"category":"Identifier"},{"range":[8,11],"category":"Identifier"},{"range":[12,26],"category":"Args","children":[{"range":[12,26],"category":"StringLiteral","children":[{"range":[12,13],"category":"StringLiteral"},{"range":[13,18],"category":"StringLiteral"},{"range":[18,19],"category":"StringLiteral"},{"range":[20,25],"category":"StringLiteral"},{"range":[25,26],"category":"StringLiteral"}]}]}]}]}]}],"range":[0,28],"hasChanges":false},{"number":1,"terms":[{"range":[0,29],"category":"Program","children":[{"range":[0,28],"category":"ExpressionStatements","children":[{"range":[0,27],"category":"MethodCall","children":[{"range":[0,7],"category":"Identifier"},{"range":[8,11],"category":"Identifier"},{"range":[12,26],"category":"Args","children":[{"range":[12,26],"category":"StringLiteral","children":[{"range":[12,13],"category":"StringLiteral"},{"range":[13,18],"category":"StringLiteral"},{"range":[18,19],"category":"StringLiteral"},{"range":[20,25],"category":"StringLiteral"},{"range":[25,26],"category":"StringLiteral"}]}]}]}]}]}],"range":[0,29],"hasChanges":false}],[{"number":2,"terms":[{"range":[29,30],"category":"Program","children":[]}],"range":[29,30],"hasChanges":false}],[{"number":3,"terms":[{"range":[30,55],"category":"Program","children":[{"patch":"insert","range":[30,55],"category":"ExpressionStatements","children":[{"range":[30,54],"category":"MethodCall","children":[{"range":[30,37],"category":"Identifier"},{"range":[38,41],"category":"Identifier"},{"range":[42,53],"category":"Args","children":[{"range":[42,53],"category":"StringLiteral","children":[{"range":[42,43],"category":"StringLiteral"},{"range":[43,52],"category":"StringLiteral"},{"range":[52,53],"category":"StringLiteral"}]}]}]}]}]}],"range":[30,55],"hasChanges":true}]],"oids":["",""],"paths":["test/diffs/no-newline-at-eof.A.js","test/diffs/no-newline-at-eof.B.js"]}
|
||||
{"rows":[[{"number":1,"terms":[{"range":[0,28],"category":"Program","children":[{"range":[0,28],"category":"ExpressionStatements","children":[{"range":[0,27],"category":"MethodCall","children":[{"range":[0,7],"category":"Identifier"},{"range":[8,11],"category":"Identifier"},{"range":[12,26],"category":"Args","children":[{"range":[12,26],"category":"StringLiteral","children":[{"range":[12,13],"category":"StringLiteral"},{"range":[13,18],"category":"StringLiteral"},{"range":[18,19],"category":"StringLiteral"},{"range":[20,25],"category":"StringLiteral"},{"range":[25,26],"category":"StringLiteral"}]}]}]}]}]}],"range":[0,28],"hasChanges":false},{"number":1,"terms":[{"range":[0,29],"category":"Program","children":[{"range":[0,28],"category":"ExpressionStatements","children":[{"range":[0,27],"category":"MethodCall","children":[{"range":[0,7],"category":"Identifier"},{"range":[8,11],"category":"Identifier"},{"range":[12,26],"category":"Args","children":[{"range":[12,26],"category":"StringLiteral","children":[{"range":[12,13],"category":"StringLiteral"},{"range":[13,18],"category":"StringLiteral"},{"range":[18,19],"category":"StringLiteral"},{"range":[20,25],"category":"StringLiteral"},{"range":[25,26],"category":"StringLiteral"}]}]}]}]}]}],"range":[0,29],"hasChanges":false}],[{"number":2,"terms":[{"range":[29,30],"category":"Program","children":[]}],"range":[29,30],"hasChanges":false}],[{"number":3,"terms":[{"range":[30,55],"category":"Program","children":[{"patch":"insert","range":[30,55],"category":"ExpressionStatements","children":[{"range":[30,54],"category":"MethodCall","children":[{"range":[30,37],"category":"Identifier"},{"range":[38,41],"category":"Identifier"},{"range":[42,53],"category":"Args","children":[{"range":[42,53],"category":"StringLiteral","children":[{"range":[42,43],"category":"StringLiteral"},{"range":[43,52],"category":"StringLiteral"},{"range":[52,53],"category":"StringLiteral"}]}]}]}]}]}],"range":[30,55],"hasChanges":true}]],"oids":["0000000000000000000000000000000000000000","0000000000000000000000000000000000000000"],"paths":["test/diffs/no-newline-at-eof.A.js","test/diffs/no-newline-at-eof.B.js"]}
|
@ -1,5 +1,5 @@
|
||||
diff --git a/test/diffs/no-newline-at-eof.A.js b/test/diffs/no-newline-at-eof.B.js
|
||||
index .. 100644
|
||||
index 0000000000000000000000000000000000000000..0000000000000000000000000000000000000000 100644
|
||||
--- a/test/diffs/no-newline-at-eof.A.js
|
||||
+++ b/test/diffs/no-newline-at-eof.B.js
|
||||
@@ -1,1 +1,3 @@
|
||||
|
Loading…
Reference in New Issue
Block a user