From 7ba5607cc858885ae2783c4492f5f348b10311e7 Mon Sep 17 00:00:00 2001 From: joshvera Date: Wed, 5 Oct 2016 17:27:45 -0400 Subject: [PATCH 01/27] Add source spans to terms --- src/DiffSummary.hs | 10 +++++----- src/Diffing.hs | 20 ++++++++++---------- src/Language.hs | 17 ++++++++++------- src/Language/C.hs | 14 ++++++++------ src/Language/JavaScript.hs | 26 +++++++++++++++----------- src/Language/Markdown.hs | 21 +++++++++++++-------- src/Renderer/JSON.hs | 2 +- src/Renderer/Summary.hs | 3 ++- src/Source.hs | 10 +++++++++- src/Syntax.hs | 3 +-- src/TreeSitter.hs | 10 ++++++---- 11 files changed, 80 insertions(+), 56 deletions(-) diff --git a/src/DiffSummary.hs b/src/DiffSummary.hs index 250260cd8..dc531592a 100644 --- a/src/DiffSummary.hs +++ b/src/DiffSummary.hs @@ -64,7 +64,7 @@ data DiffSummary a = DiffSummary { } deriving (Eq, Functor, Show, Generic) -- Returns a list of diff summary texts given two source blobs and a diff. -diffSummaries :: (HasCategory leaf, HasField fields Category, HasField fields Range) => Both SourceBlob -> SyntaxDiff leaf fields -> [Either Text Text] +diffSummaries :: (HasCategory leaf, HasField fields Category, HasField fields Range, HasField fields SourceSpan) => Both SourceBlob -> SyntaxDiff leaf fields -> [Either Text Text] diffSummaries blobs diff = summaryToTexts =<< diffToDiffSummaries (source <$> blobs) diff -- Takes a 'DiffSummary' and returns a list of summary texts representing the LeafInfos @@ -73,7 +73,7 @@ summaryToTexts :: DiffSummary DiffInfo -> [Either Text Text] summaryToTexts DiffSummary{..} = runJoin . fmap (show . (<+> parentContexts parentAnnotation)) <$> (Join <$> summaries patch) -- Returns a list of 'DiffSummary' given two source blobs and a diff. -diffToDiffSummaries :: (HasCategory leaf, HasField fields Category, HasField fields Range) => Both (Source Char) -> SyntaxDiff leaf fields -> [DiffSummary DiffInfo] +diffToDiffSummaries :: (HasCategory leaf, HasField fields Category, HasField fields Range, HasField fields SourceSpan) => Both (Source Char) -> SyntaxDiff leaf fields -> [DiffSummary DiffInfo] diffToDiffSummaries sources = para $ \diff -> let diff' = free (Prologue.fst <$> diff) @@ -170,7 +170,7 @@ toTermName source term = case unwrap term of S.Object kvs -> "{ " <> intercalate ", " (toTermName' <$> kvs) <> " }" S.Pair a _ -> toTermName' a <> ": …" S.Return expr -> maybe "empty" toTermName' expr - S.Error _ _ -> termNameFromSource term + S.Error _ -> termNameFromSource term S.If expr _ _ -> termNameFromSource expr S.For clauses _ -> termNameFromChildren term clauses S.While expr _ -> toTermName' expr @@ -209,13 +209,13 @@ parentContexts contexts = hsep $ either identifiableDoc annotatableDoc <$> conte toDoc :: Text -> Doc toDoc = string . toS -termToDiffInfo :: (HasCategory leaf, HasField fields Category, HasField fields Range) => Source Char -> SyntaxTerm leaf fields -> DiffInfo +termToDiffInfo :: (HasCategory leaf, HasField fields Category, HasField fields Range, HasField fields SourceSpan) => Source Char -> SyntaxTerm leaf fields -> DiffInfo termToDiffInfo blob term = case unwrap term of S.Indexed children -> BranchInfo (termToDiffInfo' <$> children) (toCategoryName term) BIndexed S.Fixed children -> BranchInfo (termToDiffInfo' <$> children) (toCategoryName term) BFixed S.AnonymousFunction _ _ -> LeafInfo "anonymous function" (toTermName' term) Commented cs leaf -> BranchInfo (termToDiffInfo' <$> cs <> maybeToList leaf) (toCategoryName term) BCommented - S.Error sourceSpan _ -> ErrorInfo sourceSpan (toTermName' term) + S.Error _ -> ErrorInfo (getField $ extract term) (toTermName' term) _ -> LeafInfo (toCategoryName term) (toTermName' term) where toTermName' = toTermName blob termToDiffInfo' = termToDiffInfo blob diff --git a/src/Diffing.hs b/src/Diffing.hs index a48af352b..15ac1cf35 100644 --- a/src/Diffing.hs +++ b/src/Diffing.hs @@ -36,6 +36,7 @@ import Text.Parser.TreeSitter.Language import qualified Data.Text as T import Data.Aeson (toJSON, toEncoding) import Data.Aeson.Encoding (encodingToLazyByteString) +import SourceSpan -- | Given a parser and renderer, diff two sources and return the rendered -- | result. @@ -68,7 +69,7 @@ diffFiles parser renderer sourceBlobs = do _ -> Nothing) -- | Return a parser based on the file extension (including the "."). -parserForType :: Text -> Parser (Syntax Text) (Record '[Range, Category]) +parserForType :: Text -> Parser (Syntax Text) (Record '[Range, Category, SourceSpan]) parserForType mediaType = case languageForType mediaType of Just C -> treeSitterParser C ts_language_c Just JavaScript -> treeSitterParser JavaScript ts_language_javascript @@ -77,20 +78,19 @@ parserForType mediaType = case languageForType mediaType of _ -> lineByLineParser -- | A fallback parser that treats a file simply as rows of strings. -lineByLineParser :: Parser (Syntax Text) (Record '[Range, Category]) -lineByLineParser blob = pure . cofree . root $ case foldl' annotateLeaves ([], 0) lines of +lineByLineParser :: Parser (Syntax Text) (Record '[Range, Category, SourceSpan]) +lineByLineParser SourceBlob{..} = pure . cofree . root $ case foldl' annotateLeaves ([], 0) lines of (leaves, _) -> cofree <$> leaves where - input = source blob - lines = actualLines input - root children = (Range 0 (length input) .: Program .: RNil) :< Indexed children - leaf charIndex line = (Range charIndex (charIndex + T.length line) .: Program .: RNil) :< Leaf line + lines = actualLines source + root children = (Range 0 (length source) .: Program .: sourceRangeToSpan source (toS path) (Range 0 (length source)) .: RNil) :< Indexed children + leaf charIndex line = (Range charIndex (charIndex + T.length line) .: Program .: sourceRangeToSpan source (toS path) (Range charIndex (charIndex + T.length line)) .: RNil) :< Leaf line annotateLeaves (accum, charIndex) line = (accum <> [ leaf charIndex (toText line) ] , charIndex + length line) toText = T.pack . Source.toString -- | Return the parser that should be used for a given path. -parserForFilepath :: FilePath -> Parser (Syntax Text) (Record '[Cost, Range, Category]) +parserForFilepath :: FilePath -> Parser (Syntax Text) (Record '[Cost, Range, Category, SourceSpan]) parserForFilepath path blob = decorateTerm termCostDecorator <$> parserForType (toS (takeExtension path)) blob -- | Transcode a file to a unicode source. @@ -128,7 +128,7 @@ diffCostWithCachedTermCosts diff = unCost $ case runFree diff of Pure patch -> sum (cost . extract <$> patch) -- | Returns a rendered diff given a parser, diff arguments and two source blobs. -textDiff :: (HasField fields Category, HasField fields Cost, HasField fields Range) => Parser (Syntax Text) (Record fields) -> DiffArguments -> Both SourceBlob -> IO Output +textDiff :: (HasField fields SourceSpan, HasField fields Category, HasField fields Cost, HasField fields Range) => Parser (Syntax Text) (Record fields) -> DiffArguments -> Both SourceBlob -> IO Output textDiff parser arguments = diffFiles parser $ case format arguments of Split -> split Patch -> patch @@ -144,7 +144,7 @@ truncatedDiff arguments sources = pure $ case format arguments of Summary -> SummaryOutput mempty -- | Prints a rendered diff to stdio or a filepath given a parser, diff arguments and two source blobs. -printDiff :: (HasField fields Category, HasField fields Cost, HasField fields Range) => Parser (Syntax Text) (Record fields) -> DiffArguments -> Both SourceBlob -> IO () +printDiff :: (HasField fields SourceSpan, HasField fields Category, HasField fields Cost, HasField fields Range) => Parser (Syntax Text) (Record fields) -> DiffArguments -> Both SourceBlob -> IO () printDiff parser arguments sources = do rendered <- textDiff parser arguments sources let renderedText = case rendered of diff --git a/src/Language.hs b/src/Language.hs index 151cc53d0..0728a1dba 100644 --- a/src/Language.hs +++ b/src/Language.hs @@ -45,11 +45,14 @@ termConstructor -> IO SourceSpan -- ^ The span that the term occupies. This is passed in 'IO' to guarantee some access constraints & encourage its use only when needed (improving performance). -> Text -- ^ The name of the production for this node. -> Range -- ^ The character range that the term occupies. - -> [Term (S.Syntax Text) (Record '[Range, Category])] -- ^ The child nodes of the term. - -> IO (Term (S.Syntax Text) (Record '[Range, Category])) -- ^ The resulting term, in IO. + -> [Term (S.Syntax Text) (Record '[Range, Category, SourceSpan])] -- ^ The child nodes of the term. + -> IO (Term (S.Syntax Text) (Record '[Range, Category, SourceSpan])) -- ^ The resulting term, in IO. termConstructor source sourceSpan name range children = - withDefaultInfo <$> case (name, children) of - ("ERROR", _) -> S.Error <$> sourceSpan <*> pure children - (_, []) -> S.Leaf <$> pure (toText $ slice range source) - _ -> S.Indexed <$> pure children - where withDefaultInfo syntax = cofree ((range .: Other name .: RNil) :< syntax) + withDefaultInfo $ case (name, children) of + ("ERROR", _) -> S.Error children + (_, []) -> S.Leaf (toText $ slice range source) + _ -> S.Indexed children + where + withDefaultInfo syntax = do + sourceSpan' <- sourceSpan + pure $! cofree ((range .: Other name .: sourceSpan' .: RNil) :< syntax) diff --git a/src/Language/C.hs b/src/Language/C.hs index 0cf8d2d52..a8a3825f0 100644 --- a/src/Language/C.hs +++ b/src/Language/C.hs @@ -15,15 +15,17 @@ termConstructor -> IO SourceSpan -- ^ The span that the term occupies. This is passed in 'IO' to guarantee some access constraints & encourage its use only when needed (improving performance). -> Text -- ^ The name of the production for this node. -> Range -- ^ The character range that the term occupies. - -> [Term (Syntax Text) (Record '[Range, Category])] -- ^ The child nodes of the term. - -> IO (Term (Syntax Text) (Record '[Range, Category])) -- ^ The resulting term, in IO. + -> [Term (Syntax Text) (Record '[Range, Category, SourceSpan])] -- ^ The child nodes of the term. + -> IO (Term (Syntax Text) (Record '[Range, Category, SourceSpan])) -- ^ The resulting term, in IO. termConstructor source sourceSpan name range children - | name == "ERROR" = sourceSpan >>= withDefaultInfo . (`S.Error` children) + | name == "ERROR" = withDefaultInfo (S.Error children) | otherwise = withDefaultInfo $ case (name, children) of (_, []) -> S.Leaf . toText $ slice range source _ -> S.Indexed children - where withDefaultInfo syntax = pure $! cofree ((range .: categoryForCProductionName name .: RNil) :< syntax) + where + withDefaultInfo syntax = do + sourceSpan' <- sourceSpan + pure $! cofree ((range .: categoryForCProductionName name .: sourceSpan' .: RNil) :< syntax) categoryForCProductionName :: Text -> Category -categoryForCProductionName name = case name of - _ -> Other name +categoryForCProductionName name = Other name diff --git a/src/Language/JavaScript.hs b/src/Language/JavaScript.hs index 42deb23a6..76510a9e0 100644 --- a/src/Language/JavaScript.hs +++ b/src/Language/JavaScript.hs @@ -23,10 +23,10 @@ termConstructor -> IO SourceSpan -- ^ The span that the term occupies. This is passed in 'IO' to guarantee some access constraints & encourage its use only when needed (improving performance). -> Text -- ^ The name of the production for this node. -> Range -- ^ The character range that the term occupies. - -> [Term (S.Syntax Text) (Record '[Range, Category])] -- ^ The child nodes of the term. - -> IO (Term (S.Syntax Text) (Record '[Range, Category])) -- ^ The resulting term, in IO. + -> [Term (S.Syntax Text) (Record '[Range, Category, SourceSpan])] -- ^ The child nodes of the term. + -> IO (Term (S.Syntax Text) (Record '[Range, Category, SourceSpan])) -- ^ The resulting term, in IO. termConstructor source sourceSpan name range children - | name == "ERROR" = sourceSpan >>= withDefaultInfo . (`S.Error` children) + | name == "ERROR" = withDefaultInfo (S.Error children) | otherwise = withDefaultInfo $ case (name, children) of ("return_statement", _) -> S.Return (listToMaybe children) ("assignment", [ identifier, value ]) -> S.Assignment identifier value @@ -37,16 +37,16 @@ termConstructor source sourceSpan name range children S.Indexed rest -> S.Indexed $ a : rest _ -> S.Indexed children ("function_call", _) -> case runCofree <$> children of - [ (_ :< S.MemberAccess{..}), (_ :< S.Args args) ] -> S.MethodCall memberId property args - [ (_ :< S.MemberAccess{..}) ] -> S.MethodCall memberId property [] - [ function, (_ :< S.Args args) ] -> S.FunctionCall (cofree function) args + [ _ :< S.MemberAccess{..}, _ :< S.Args args ] -> S.MethodCall memberId property args + [ _ :< S.MemberAccess{..} ] -> S.MethodCall memberId property [] + [ function, _ :< S.Args args ] -> S.FunctionCall (cofree function) args (x:xs) -> S.FunctionCall (cofree x) (cofree <$> xs) _ -> S.Indexed children - ("ternary", (condition:cases)) -> S.Ternary condition cases + ("ternary", condition : cases) -> S.Ternary condition cases ("arguments", _) -> S.Args children ("var_assignment", [ x, y ]) -> S.VarAssignment x y ("var_declaration", _) -> S.Indexed $ toVarDecl <$> children - ("switch_statement", (expr:rest)) -> S.Switch expr rest + ("switch_statement", expr : rest) -> S.Switch expr rest ("case", [ expr, body ]) -> S.Case expr body ("object", _) -> S.Object $ foldMap toTuple children ("pair", _) -> S.Fixed children @@ -78,8 +78,12 @@ termConstructor source sourceSpan name range children _ -> S.Indexed children (_, []) -> S.Leaf . toText $ slice range source _ -> S.Indexed children - where withDefaultInfo syntax@(S.MethodCall _ _ _) = pure $! cofree ((range .: MethodCall .: RNil) :< syntax) - withDefaultInfo syntax = pure $! cofree ((range .: categoryForJavaScriptProductionName name .: RNil) :< syntax) + where + withDefaultInfo syntax = do + sourceSpan' <- sourceSpan + pure $! case syntax of + S.MethodCall{} -> cofree ((range .: MethodCall .: sourceSpan' .: RNil) :< syntax) + _ -> cofree ((range .: categoryForJavaScriptProductionName name .: sourceSpan' .: RNil) :< syntax) categoryForJavaScriptProductionName :: Text -> Category categoryForJavaScriptProductionName name = case name of @@ -145,7 +149,7 @@ categoryForJavaScriptProductionName name = case name of _ -> Other name toVarDecl :: (HasField fields Category) => Term (S.Syntax Text) (Record fields) -> Term (S.Syntax Text) (Record fields) -toVarDecl child = cofree $ (setCategory (extract child) VarDecl :< S.VarDecl child) +toVarDecl child = cofree $ setCategory (extract child) VarDecl :< S.VarDecl child toTuple :: Term (S.Syntax Text) (Record fields) -> [Term (S.Syntax Text) (Record fields)] toTuple child | S.Indexed [key,value] <- unwrap child = [cofree (extract child :< S.Pair key value)] diff --git a/src/Language/Markdown.hs b/src/Language/Markdown.hs index 52f48cd86..c2f3f90fa 100644 --- a/src/Language/Markdown.hs +++ b/src/Language/Markdown.hs @@ -12,16 +12,21 @@ import Source import SourceSpan import Syntax -cmarkParser :: Parser (Syntax Text) (Record '[Range, Category]) -cmarkParser SourceBlob{..} = pure . toTerm (totalRange source) $ commonmarkToNode [ optSourcePos, optSafe ] (toText source) - where toTerm :: Range -> Node -> Cofree (Syntax Text) (Record '[Range, Category]) - toTerm within (Node position t children) = let range = maybe within (sourceSpanToRange source . toSpan) position in cofree $ (range .: toCategory t .: RNil) :< case t of +cmarkParser :: Parser (Syntax Text) (Record '[Range, Category, SourceSpan]) +cmarkParser SourceBlob{..} = pure . toTerm (totalRange source) (sourceRangeToSpan source (toS path) $ totalRange source) $ commonmarkToNode [ optSourcePos, optSafe ] (toText source) + where toTerm :: Range -> SourceSpan -> Node -> Cofree (Syntax Text) (Record '[Range, Category, SourceSpan]) + toTerm within withinSpan (Node position t children) = + let + range = maybe within (sourceSpanToRange source . toSpan) position + span = maybe withinSpan toSpan position + in + cofree $ (range .: toCategory t .: span .: RNil) :< case t of -- Leaves CODE text -> Leaf text TEXT text -> Leaf text CODE_BLOCK _ text -> Leaf text -- Branches - _ -> Indexed (toTerm range <$> children) + _ -> Indexed (toTerm range span <$> children) toCategory :: NodeType -> Category toCategory (TEXT _) = Other "text" @@ -29,10 +34,10 @@ cmarkParser SourceBlob{..} = pure . toTerm (totalRange source) $ commonmarkToNod toCategory (HTML_BLOCK _) = Other "html" toCategory (HTML_INLINE _) = Other "html" toCategory (HEADING _) = Other "heading" - toCategory (LIST (ListAttributes{..})) = Other $ case listType of + toCategory (LIST ListAttributes{..}) = Other $ case listType of BULLET_LIST -> "unordered list" ORDERED_LIST -> "ordered list" - toCategory (LINK{}) = Other "link" - toCategory (IMAGE{}) = Other "image" + toCategory LINK{} = Other "link" + toCategory IMAGE{} = Other "image" toCategory t = Other (show t) toSpan PosInfo{..} = SourceSpan "" (SourcePos (pred startLine) (pred startColumn)) (SourcePos (pred endLine) endColumn) diff --git a/src/Renderer/JSON.hs b/src/Renderer/JSON.hs index a4c9aaa06..6e3866312 100644 --- a/src/Renderer/JSON.hs +++ b/src/Renderer/JSON.hs @@ -94,7 +94,7 @@ termFields info syntax = "range" .= characterRange info : "category" .= category S.Constructor expr -> [ "constructorExpression" .= expr ] S.Comment _ -> [] S.Commented comments child -> childrenFields (comments <> maybeToList child) - S.Error sourceSpan c -> [ "sourceSpan" .= sourceSpan ] <> childrenFields c + S.Error c -> childrenFields c S.Throw c -> [ "throwExpression" .= c ] S.Try body catch finally -> [ "tryBody" .= body ] <> [ "tryCatch" .= catch ] <> [ "tryFinally" .= finally ] S.Array c -> childrenFields c diff --git a/src/Renderer/Summary.hs b/src/Renderer/Summary.hs index f021e84ed..384c676ae 100644 --- a/src/Renderer/Summary.hs +++ b/src/Renderer/Summary.hs @@ -9,8 +9,9 @@ import Range import DiffSummary import Data.Map as Map hiding (null) import Source +import SourceSpan -summary :: (HasField fields Category, HasField fields Range) => Renderer (Record fields) +summary :: (HasField fields Category, HasField fields Range, HasField fields SourceSpan) => Renderer (Record fields) summary blobs diff = SummaryOutput $ Map.fromList [ ("changes", changes), ("errors", errors) diff --git a/src/Source.hs b/src/Source.hs index 04cc5f379..ae90e71c8 100644 --- a/src/Source.hs +++ b/src/Source.hs @@ -91,7 +91,7 @@ actualLineRanges :: Range -> Source Char -> [Range] actualLineRanges range = drop 1 . scanl toRange (Range (start range) (start range)) . actualLines . slice range where toRange previous string = Range (end previous) $ end previous + length string --- | Compute the character range corresponding to a given SourceSpan within a Source. +-- | Compute the character range given a Source and a SourceSpan. sourceSpanToRange :: Source Char -> SourceSpan -> Range sourceSpanToRange source SourceSpan{..} = Range start end where start = sumLengths leadingRanges + column spanStart @@ -99,6 +99,14 @@ sourceSpanToRange source SourceSpan{..} = Range start end (leadingRanges, remainingRanges) = splitAt (line spanStart) (actualLineRanges (totalRange source) source) sumLengths = sum . fmap (\ Range{..} -> end - start) +sourceRangeToSpan :: Source Char -> Text -> Range -> SourceSpan +sourceRangeToSpan source name range@Range{} = SourceSpan name startPos endPos + where startPos = maybe (SourcePos 0 0) (toStartPos 0) (head lineRanges) + endPos = toEndPos (length lineRanges) (last lineRanges) + lineRanges = actualLineRanges range source + toStartPos line range = SourcePos line (start range) + toEndPos line range = SourcePos line (end range) + instance Semigroup (Source a) where Source a <> Source b = Source (a Vector.++ b) diff --git a/src/Syntax.hs b/src/Syntax.hs index d4d6355f4..229499422 100644 --- a/src/Syntax.hs +++ b/src/Syntax.hs @@ -5,7 +5,6 @@ import Prologue import Data.Mergeable import GHC.Generics import Test.QuickCheck hiding (Fixed) -import SourceSpan -- | A node in an abstract syntax tree. -- @@ -57,7 +56,7 @@ data Syntax a f | Comment a -- | A term preceded or followed by any number of comments. | Commented [f] (Maybe f) - | Error SourceSpan [f] + | Error [f] | For [f] f | DoWhile { doWhileBody :: f, doWhileExpr :: f } | While { whileExpr :: f, whileBody :: f } diff --git a/src/TreeSitter.hs b/src/TreeSitter.hs index 917488c82..b1c251ab9 100644 --- a/src/TreeSitter.hs +++ b/src/TreeSitter.hs @@ -19,7 +19,7 @@ import SourceSpan import Info -- | Returns a TreeSitter parser for the given language and TreeSitter grammar. -treeSitterParser :: Language -> Ptr TS.Language -> Parser (Syntax.Syntax Text) (Record '[Range, Category]) +treeSitterParser :: Language -> Ptr TS.Language -> Parser (Syntax.Syntax Text) (Record '[Range, Category, SourceSpan]) treeSitterParser language grammar blob = do document <- ts_document_make ts_document_set_language document grammar @@ -31,7 +31,7 @@ treeSitterParser language grammar blob = do pure term) -- | Return a parser for a tree sitter language & document. -documentToTerm :: Language -> Ptr Document -> Parser (Syntax.Syntax Text) (Record '[Range, Category]) +documentToTerm :: Language -> Ptr Document -> Parser (Syntax.Syntax Text) (Record '[Range, Category, SourceSpan]) documentToTerm language document SourceBlob{..} = alloca $ \ root -> do ts_document_root_node_p document root toTerm root @@ -43,9 +43,11 @@ documentToTerm language document SourceBlob{..} = alloca $ \ root -> do let range = Range { start = fromIntegral $ ts_node_p_start_char node, end = fromIntegral $ ts_node_p_end_char node } - let sourceSpan = SourceSpan { spanName = toS path + let sourceSpan = SourceSpan { + spanName = toS path , spanStart = SourcePos (fromIntegral $! ts_node_p_start_point_row node) (fromIntegral $! ts_node_p_start_point_column node) - , spanEnd = SourcePos (fromIntegral $! ts_node_p_end_point_row node) (fromIntegral $! ts_node_p_end_point_column node) } + , spanEnd = SourcePos (fromIntegral $! ts_node_p_end_point_row node) (fromIntegral $! ts_node_p_end_point_column node) + } -- Note: The strict application here is semantically important. -- Without it, we may not evaluate the range until after we’ve exited From 224aba6c1f0678ca010476790ed345d5899ea7fe Mon Sep 17 00:00:00 2001 From: joshvera Date: Wed, 5 Oct 2016 17:40:49 -0400 Subject: [PATCH 02/27] Expose SourceSpan/SourcePos from Info --- src/Info.hs | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/src/Info.hs b/src/Info.hs index 30410252a..7dc38bdde 100644 --- a/src/Info.hs +++ b/src/Info.hs @@ -1,10 +1,11 @@ {-# LANGUAGE DataKinds, GeneralizedNewtypeDeriving #-} -module Info (Range(..), characterRange, setCharacterRange, Category(..), category, setCategory, Cost(..), cost, setCost) where +module Info (Range(..), characterRange, setCharacterRange, Category(..), category, setCategory, Cost(..), cost, setCost, SourceSpan(..), SourcePos(..)) where import Data.Record import Prologue import Category import Range +import SourceSpan import Test.QuickCheck newtype Cost = Cost { unCost :: Int } From b7df878c4b4bf4a037e3d6415a417abedee8a976 Mon Sep 17 00:00:00 2001 From: joshvera Date: Wed, 5 Oct 2016 17:41:00 -0400 Subject: [PATCH 03/27] Update specs --- test/CorpusSpec.hs | 2 +- test/DiffSummarySpec.hs | 18 +++++++++--------- 2 files changed, 10 insertions(+), 10 deletions(-) diff --git a/test/CorpusSpec.hs b/test/CorpusSpec.hs index 7f46d9a90..a6cc41535 100644 --- a/test/CorpusSpec.hs +++ b/test/CorpusSpec.hs @@ -75,7 +75,7 @@ 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 '[Vector.Vector Double, Cost, Range, Category]) -> Both (Maybe FilePath) -> Maybe FilePath -> (Maybe Verbatim -> Maybe Verbatim -> Expectation) -> Expectation +testDiff :: Renderer (Record '[Vector.Vector Double, Cost, Range, Category, SourceSpan]) -> Both (Maybe FilePath) -> Maybe FilePath -> (Maybe Verbatim -> Maybe Verbatim -> Expectation) -> Expectation testDiff renderer paths diff matcher = do sources <- traverse (traverse readAndTranscodeFile) paths actual <- fmap Verbatim <$> traverse ((pure . concatOutputs . pure) <=< diffFiles' sources) parser diff --git a/test/DiffSummarySpec.hs b/test/DiffSummarySpec.hs index c487ab7ef..326050682 100644 --- a/test/DiffSummarySpec.hs +++ b/test/DiffSummarySpec.hs @@ -21,13 +21,13 @@ import Test.Hspec (Spec, describe, it, parallel) import Test.Hspec.Expectations.Pretty import Test.Hspec.QuickCheck -arrayInfo :: Record '[Category, Range] -arrayInfo = ArrayLiteral .: Range 0 3 .: RNil +arrayInfo :: Record '[Category, Range, SourceSpan] +arrayInfo = ArrayLiteral .: Range 0 3 .: SourceSpan "" (SourcePos 1 0) (SourcePos 1 3) .: RNil -literalInfo :: Record '[Category, Range] -literalInfo = StringLiteral .: Range 1 2 .: RNil +literalInfo :: Record '[Category, Range, SourceSpan] +literalInfo = StringLiteral .: Range 1 2 .: SourceSpan "" (SourcePos 1 2) (SourcePos 1 3) .: RNil -testDiff :: Diff (Syntax Text) (Record '[Category, Range]) +testDiff :: Diff (Syntax Text) (Record '[Category, Range, SourceSpan]) testDiff = free $ Free (pure arrayInfo :< Indexed [ free $ Pure (Insert (cofree $ literalInfo :< Leaf "\"a\"")) ]) testSummary :: DiffSummary DiffInfo @@ -46,13 +46,13 @@ spec = parallel $ do diffSummaries blobs testDiff `shouldBe` [ Right $ "Added the \"a\" string" ] prop "equal terms produce identity diffs" $ - \ a -> let term = defaultFeatureVectorDecorator (category . headF) (toTerm (a :: ArbitraryTerm Text (Record '[Category, Range]))) in + \ a -> let term = defaultFeatureVectorDecorator (category . headF) (toTerm (a :: ArbitraryTerm Text (Record '[Category, Range, SourceSpan]))) in diffSummaries blobs (diffTerms wrap (==) diffCost term term) `shouldBe` [] describe "DiffInfo" $ do prop "patches in summaries match the patches in diffs" $ \a -> let - diff = (toDiff (a :: ArbitraryDiff Text (Record '[Category, Cost, Range]))) + diff = (toDiff (a :: ArbitraryDiff Text (Record '[Category, Cost, Range, SourceSpan]))) summaries = diffToDiffSummaries (source <$> blobs) diff patches = toList diff in @@ -61,14 +61,14 @@ spec = parallel $ do (() <$ branchPatches, () <$ otherPatches) `shouldBe` (() <$ branchDiffPatches, () <$ otherDiffPatches) prop "generates one LeafInfo for each child in an arbitrary branch patch" $ \a -> let - diff = (toDiff (a :: ArbitraryDiff Text (Record '[Category, Range]))) + diff = (toDiff (a :: ArbitraryDiff Text (Record '[Category, Range, SourceSpan]))) diffInfoPatches = patch <$> diffToDiffSummaries (source <$> blobs) diff syntaxPatches = toList diff extractLeaves :: DiffInfo -> [DiffInfo] extractLeaves (BranchInfo children _ _) = join $ extractLeaves <$> children extractLeaves leaf = [ leaf ] - extractDiffLeaves :: Term (Syntax Text) (Record '[Category, Range]) -> [ Term (Syntax Text) (Record '[Category, Range]) ] + extractDiffLeaves :: Term (Syntax Text) (Record '[Category, Range, SourceSpan]) -> [ Term (Syntax Text) (Record '[Category, Range, SourceSpan]) ] extractDiffLeaves term = case unwrap term of (Indexed children) -> join $ extractDiffLeaves <$> children (Fixed children) -> join $ extractDiffLeaves <$> children From 3def8b09547a90aec14d465114ebc3c40aab5083 Mon Sep 17 00:00:00 2001 From: joshvera Date: Wed, 5 Oct 2016 17:45:24 -0400 Subject: [PATCH 04/27] Remove SourceSpan imports --- src/Language.hs | 1 - src/Language/C.hs | 1 - src/Language/JavaScript.hs | 1 - src/Language/Markdown.hs | 1 - 4 files changed, 4 deletions(-) diff --git a/src/Language.hs b/src/Language.hs index 0728a1dba..1a7246c5a 100644 --- a/src/Language.hs +++ b/src/Language.hs @@ -5,7 +5,6 @@ import Data.Record import Info import Prologue import Source -import SourceSpan import qualified Syntax as S import Term diff --git a/src/Language/C.hs b/src/Language/C.hs index a8a3825f0..d7516ab01 100644 --- a/src/Language/C.hs +++ b/src/Language/C.hs @@ -5,7 +5,6 @@ import Data.Record import Info import Prologue import Source -import SourceSpan import Syntax import qualified Syntax as S import Term diff --git a/src/Language/JavaScript.hs b/src/Language/JavaScript.hs index 76510a9e0..070683e41 100644 --- a/src/Language/JavaScript.hs +++ b/src/Language/JavaScript.hs @@ -5,7 +5,6 @@ import Data.Record import Info import Prologue import Source -import SourceSpan import qualified Syntax as S import Term diff --git a/src/Language/Markdown.hs b/src/Language/Markdown.hs index c2f3f90fa..1dfab6cd9 100644 --- a/src/Language/Markdown.hs +++ b/src/Language/Markdown.hs @@ -9,7 +9,6 @@ import Parser import Prologue import Range import Source -import SourceSpan import Syntax cmarkParser :: Parser (Syntax Text) (Record '[Range, Category, SourceSpan]) From 7121ec7fe05a1d377e964b2bcec39265c94c7029 Mon Sep 17 00:00:00 2001 From: joshvera Date: Wed, 5 Oct 2016 17:46:00 -0400 Subject: [PATCH 05/27] more imports :hocho: --- src/Diffing.hs | 1 - 1 file changed, 1 deletion(-) diff --git a/src/Diffing.hs b/src/Diffing.hs index 15ac1cf35..461873770 100644 --- a/src/Diffing.hs +++ b/src/Diffing.hs @@ -36,7 +36,6 @@ import Text.Parser.TreeSitter.Language import qualified Data.Text as T import Data.Aeson (toJSON, toEncoding) import Data.Aeson.Encoding (encodingToLazyByteString) -import SourceSpan -- | Given a parser and renderer, diff two sources and return the rendered -- | result. From ecf34e5d6eac3c88e6abc173ba38c5446c9fbe97 Mon Sep 17 00:00:00 2001 From: joshvera Date: Thu, 6 Oct 2016 13:12:40 -0400 Subject: [PATCH 06/27] Output source spans to JSON --- src/DiffSummary.hs | 85 ++++++++++++++++++++++------------------- src/Renderer.hs | 4 +- src/Renderer/Summary.hs | 11 ++++-- 3 files changed, 55 insertions(+), 45 deletions(-) diff --git a/src/DiffSummary.hs b/src/DiffSummary.hs index dc531592a..991cbd0a8 100644 --- a/src/DiffSummary.hs +++ b/src/DiffSummary.hs @@ -1,6 +1,6 @@ -{-# LANGUAGE DataKinds, TypeFamilies, ScopedTypeVariables #-} +{-# LANGUAGE DataKinds, TypeFamilies, ScopedTypeVariables, DeriveAnyClass #-} -module DiffSummary (diffSummaries, DiffSummary(..), DiffInfo(..), diffToDiffSummaries, isBranchInfo) where +module DiffSummary (diffSummaries, DiffSummary(..), DiffInfo(..), diffToDiffSummaries, isBranchInfo, isErrorSummary, JSONSummary) where import Prologue hiding (intercalate) import Diff @@ -21,6 +21,7 @@ import Text.PrettyPrint.Leijen.Text ((<+>), squotes, space, string, Doc, punctua import qualified Text.PrettyPrint.Leijen.Text as P import SourceSpan import Source +import Data.Aeson (ToJSON) data Annotatable a = Annotatable a | Unannotatable a @@ -51,7 +52,15 @@ identifiable term = isIdentifiable (unwrap term) term S.DoWhile{} -> Identifiable _ -> Unidentifiable -data DiffInfo = LeafInfo { categoryName :: Text, termName :: Text } +data JSONSummary summary span = JSONSummary { summary :: summary, span :: span } + | ErrorSummary { summary :: summary, span :: span } + deriving (ToJSON, Generic) + +isErrorSummary :: JSONSummary summary span -> Bool +isErrorSummary ErrorSummary{} = True +isErrorSummary _ = False + +data DiffInfo = LeafInfo { categoryName :: Text, termName :: Text, sourceSpan :: SourceSpan } | BranchInfo { branches :: [ DiffInfo ], categoryName :: Text, branchType :: Branch } | ErrorInfo { errorSpan :: SourceSpan, termName :: Text } deriving (Eq, Show) @@ -64,13 +73,14 @@ data DiffSummary a = DiffSummary { } deriving (Eq, Functor, Show, Generic) -- Returns a list of diff summary texts given two source blobs and a diff. -diffSummaries :: (HasCategory leaf, HasField fields Category, HasField fields Range, HasField fields SourceSpan) => Both SourceBlob -> SyntaxDiff leaf fields -> [Either Text Text] +diffSummaries :: (HasCategory leaf, HasField fields Category, HasField fields Range, HasField fields SourceSpan) => Both SourceBlob -> SyntaxDiff leaf fields -> [JSONSummary Text (These SourceSpan SourceSpan)] diffSummaries blobs diff = summaryToTexts =<< diffToDiffSummaries (source <$> blobs) diff -- Takes a 'DiffSummary' and returns a list of summary texts representing the LeafInfos -- in that 'DiffSummary'. -summaryToTexts :: DiffSummary DiffInfo -> [Either Text Text] -summaryToTexts DiffSummary{..} = runJoin . fmap (show . (<+> parentContexts parentAnnotation)) <$> (Join <$> summaries patch) +summaryToTexts :: DiffSummary DiffInfo -> [JSONSummary Text (These SourceSpan SourceSpan)] +summaryToTexts DiffSummary{..} = (\jsonSummary -> + jsonSummary { summary = show $ summary jsonSummary <+> parentContexts parentAnnotation }) <$> summaries patch -- Returns a list of 'DiffSummary' given two source blobs and a diff. diffToDiffSummaries :: (HasCategory leaf, HasField fields Category, HasField fields Range, HasField fields SourceSpan) => Both (Source Char) -> SyntaxDiff leaf fields -> [DiffSummary DiffInfo] @@ -89,24 +99,27 @@ diffToDiffSummaries sources = para $ \diff -> where (beforeSource, afterSource) = runJoin sources --- Returns a list of diff summary 'Docs' prefixed given a 'Patch'. -summaries :: Patch DiffInfo -> [Either Doc Doc] -summaries patch = eitherErrorOrDoc <$> patchToDoc patch - where eitherErrorOrDoc = if any hasErrorInfo patch then Left else Right - --- Flattens a patch of diff infos into a list of docs, one for every 'LeafInfo' --- or `ErrorInfo` it contains. -patchToDoc :: Patch DiffInfo -> [Doc] -patchToDoc = \case - p@(Replace i1 i2) -> zipWith (\a b -> prefixWithPatch p a <+> "with" <+> determiner i1 <+> b) (toLeafInfos i1) (toLeafInfos i2) - p@(Insert info) -> prefixWithPatch p <$> toLeafInfos info - p@(Delete info) -> prefixWithPatch p <$> toLeafInfos info +-- Flattens a patch of diff infos into a list of docs, one for every 'LeafInfo' or `ErrorInfo` it contains. +summaries :: Patch DiffInfo -> [JSONSummary Doc (These SourceSpan SourceSpan)] +summaries = \case + p@(Replace i1 i2) -> zipWith (\a b -> + JSONSummary + { + summary = summary (prefixWithPatch p This a) <+> "with" <+> determiner i1 <+> summary b + , span = These (span a) (span b) + }) (toLeafInfos i1) (toLeafInfos i2) + p@(Insert info) -> prefixWithPatch p That <$> toLeafInfos info + p@(Delete info) -> prefixWithPatch p This <$> toLeafInfos info -- Prefixes a given doc with the type of patch it represents. -prefixWithPatch :: Patch DiffInfo -> Doc -> Doc -prefixWithPatch patch = prefixWithThe (patchToPrefix patch) +prefixWithPatch :: Patch DiffInfo -> (SourceSpan -> These SourceSpan SourceSpan) -> JSONSummary Doc SourceSpan -> JSONSummary Doc (These SourceSpan SourceSpan) +prefixWithPatch patch constructor = prefixWithThe (patchToPrefix patch) where - prefixWithThe prefix doc = prefix <+> determiner' patch <+> doc + prefixWithThe prefix jsonSummary = jsonSummary + { + summary = prefix <+> determiner' patch <+> summary jsonSummary + , span = constructor (span jsonSummary) + } patchToPrefix = \case (Replace _ _) -> "Replaced" (Insert _) -> "Added" @@ -115,20 +128,20 @@ prefixWithPatch patch = prefixWithThe (patchToPrefix patch) -- Optional determiner (e.g. "the") to tie together summary statements. determiner :: DiffInfo -> Doc -determiner (LeafInfo "number" _) = "" -determiner (LeafInfo "boolean" _) = "" -determiner (LeafInfo "anonymous function" _) = "an" +determiner (LeafInfo "number" _ _) = "" +determiner (LeafInfo "boolean" _ _) = "" +determiner (LeafInfo "anonymous function" _ _) = "an" determiner (BranchInfo bs _ _) = determiner (last bs) determiner _ = "the" -toLeafInfos :: DiffInfo -> [Doc] -toLeafInfos (LeafInfo "number" termName) = pure (squotes (toDoc termName)) -toLeafInfos (LeafInfo "boolean" termName) = pure (squotes (toDoc termName)) -toLeafInfos (LeafInfo "anonymous function" termName) = pure (toDoc termName) -toLeafInfos (LeafInfo cName@"string" termName) = pure (toDoc termName <+> toDoc cName) -toLeafInfos LeafInfo{..} = pure (squotes (toDoc termName) <+> toDoc categoryName) +toLeafInfos :: DiffInfo -> [JSONSummary Doc SourceSpan] +toLeafInfos (LeafInfo "number" termName sourceSpan) = pure $ JSONSummary (squotes $ toDoc termName) sourceSpan +toLeafInfos (LeafInfo "boolean" termName sourceSpan) = pure $ JSONSummary (squotes $ toDoc termName) sourceSpan +toLeafInfos (LeafInfo "anonymous function" termName sourceSpan) = pure $ JSONSummary (toDoc termName) sourceSpan +toLeafInfos (LeafInfo cName@"string" termName sourceSpan) = pure $ JSONSummary (toDoc termName <+> toDoc cName) sourceSpan +toLeafInfos LeafInfo{..} = pure $ JSONSummary (squotes (toDoc termName) <+> toDoc categoryName) sourceSpan toLeafInfos BranchInfo{..} = toLeafInfos =<< branches -toLeafInfos err@ErrorInfo{} = pure (pretty err) +toLeafInfos err@ErrorInfo{..} = pure $ ErrorSummary (pretty err) errorSpan -- Returns a text representing a specific term given a source and a term. toTermName :: forall leaf fields. (HasCategory leaf, HasField fields Category, HasField fields Range) => Source Char -> SyntaxTerm leaf fields -> Text @@ -213,10 +226,10 @@ termToDiffInfo :: (HasCategory leaf, HasField fields Category, HasField fields R termToDiffInfo blob term = case unwrap term of S.Indexed children -> BranchInfo (termToDiffInfo' <$> children) (toCategoryName term) BIndexed S.Fixed children -> BranchInfo (termToDiffInfo' <$> children) (toCategoryName term) BFixed - S.AnonymousFunction _ _ -> LeafInfo "anonymous function" (toTermName' term) + S.AnonymousFunction _ _ -> LeafInfo "anonymous function" (toTermName' term) (getField $ extract term) Commented cs leaf -> BranchInfo (termToDiffInfo' <$> cs <> maybeToList leaf) (toCategoryName term) BCommented S.Error _ -> ErrorInfo (getField $ extract term) (toTermName' term) - _ -> LeafInfo (toCategoryName term) (toTermName' term) + _ -> LeafInfo (toCategoryName term) (toTermName' term) (getField $ extract term) where toTermName' = toTermName blob termToDiffInfo' = termToDiffInfo blob @@ -239,12 +252,6 @@ isBranchInfo info = case info of BranchInfo{} -> True _ -> False -hasErrorInfo :: DiffInfo -> Bool -hasErrorInfo info = case info of - (ErrorInfo _ _) -> True - (BranchInfo branches _ _) -> any hasErrorInfo branches - _ -> False - -- The user-facing category name of 'a'. class HasCategory a where toCategoryName :: a -> Text diff --git a/src/Renderer.hs b/src/Renderer.hs index 4ee37b426..abe2abe2d 100644 --- a/src/Renderer.hs +++ b/src/Renderer.hs @@ -20,7 +20,7 @@ data DiffArguments = DiffArguments { format :: Format, output :: Maybe FilePath data Format = Split | Patch | JSON | Summary deriving (Show) -data Output = SplitOutput Text | PatchOutput Text | JSONOutput (Map Text Value) | SummaryOutput (Map Text (Map Text [Text])) +data Output = SplitOutput Text | PatchOutput Text | JSONOutput (Map Text Value) | SummaryOutput (Map Text (Map Text [Value])) deriving (Show) -- Returns a key representing the filename. If the filenames are different, @@ -47,7 +47,7 @@ concatOutputs list | isJSON list = toS . encodingToLazyByteString . toEncoding $ concatJSON _ = mempty concatOutputs list | isSummary list = toS . encodingToLazyByteString . toEncoding $ concatSummaries list where - concatSummaries :: [Output] -> Map Text (Map Text [Text]) + concatSummaries :: [Output] -> Map Text (Map Text [Value]) concatSummaries (SummaryOutput hash : rest) = Map.unionWith (Map.unionWith (<>)) hash (concatSummaries rest) concatSummaries _ = mempty concatOutputs list | isText list = T.intercalate "\n" (toText <$> list) diff --git a/src/Renderer/Summary.hs b/src/Renderer/Summary.hs index 384c676ae..d98089467 100644 --- a/src/Renderer/Summary.hs +++ b/src/Renderer/Summary.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE TupleSections #-} +{-# LANGUAGE TupleSections, ScopedTypeVariables #-} module Renderer.Summary where import Category @@ -10,6 +10,9 @@ import DiffSummary import Data.Map as Map hiding (null) import Source import SourceSpan +import Data.These +import Data.Aeson +import Data.List as List summary :: (HasField fields Category, HasField fields Range, HasField fields SourceSpan) => Renderer (Record fields) summary blobs diff = SummaryOutput $ Map.fromList [ @@ -17,8 +20,8 @@ summary blobs diff = SummaryOutput $ Map.fromList [ ("errors", errors) ] where - changes = if null changes' then mempty else Map.singleton summaryKey changes' - errors = if null errors' then mempty else Map.singleton summaryKey errors' - (errors', changes') = partitionEithers summaries + changes = if null changes' then mempty else Map.singleton summaryKey (toJSON <$> changes') + errors = if null errors' then mempty else Map.singleton summaryKey (toJSON <$> errors') + (errors' :: [JSONSummary Text (These SourceSpan SourceSpan)], changes' :: [JSONSummary Text (These SourceSpan SourceSpan)]) = List.partition isErrorSummary summaries summaryKey = toSummaryKey (path <$> blobs) summaries = diffSummaries blobs diff From f1a1c759b038de9a52833e00a76540f7edcf48bc Mon Sep 17 00:00:00 2001 From: joshvera Date: Thu, 6 Oct 2016 14:20:58 -0400 Subject: [PATCH 07/27] Fix some test errors --- test/DiffSummarySpec.hs | 13 ++++++++----- 1 file changed, 8 insertions(+), 5 deletions(-) diff --git a/test/DiffSummarySpec.hs b/test/DiffSummarySpec.hs index 326050682..fe2b59fca 100644 --- a/test/DiffSummarySpec.hs +++ b/test/DiffSummarySpec.hs @@ -21,20 +21,23 @@ import Test.Hspec (Spec, describe, it, parallel) import Test.Hspec.Expectations.Pretty import Test.Hspec.QuickCheck +sourceSpanBetween :: (Int, Int) -> (Int, Int) -> SourceSpan +sourceSpanBetween (s1, e1) (s2, e2) = SourceSpan "" (SourcePos s1 e1) (SourcePos s2 e2) + arrayInfo :: Record '[Category, Range, SourceSpan] -arrayInfo = ArrayLiteral .: Range 0 3 .: SourceSpan "" (SourcePos 1 0) (SourcePos 1 3) .: RNil +arrayInfo = ArrayLiteral .: Range 0 3 .: sourceSpanBetween (1, 1) (1, 4) .: RNil literalInfo :: Record '[Category, Range, SourceSpan] -literalInfo = StringLiteral .: Range 1 2 .: SourceSpan "" (SourcePos 1 2) (SourcePos 1 3) .: RNil +literalInfo = StringLiteral .: Range 1 2 .: sourceSpanBetween (1, 2) (1, 3) .: RNil testDiff :: Diff (Syntax Text) (Record '[Category, Range, SourceSpan]) testDiff = free $ Free (pure arrayInfo :< Indexed [ free $ Pure (Insert (cofree $ literalInfo :< Leaf "\"a\"")) ]) testSummary :: DiffSummary DiffInfo -testSummary = DiffSummary { patch = Insert (LeafInfo "string" "a"), parentAnnotation = [] } +testSummary = DiffSummary { patch = Insert (LeafInfo "string" "a" $ sourceSpanBetween (1,1) (1, 2)), parentAnnotation = [] } replacementSummary :: DiffSummary DiffInfo -replacementSummary = DiffSummary { patch = Replace (LeafInfo "string" "a") (LeafInfo "symbol" "b"), parentAnnotation = [Left (Info.FunctionCall, "foo")] } +replacementSummary = DiffSummary { patch = Replace (LeafInfo "string" "a" $ sourceSpanBetween (1,1) (1, 2)) (LeafInfo "symbol" "b" $ sourceSpanBetween (1,1) (1, 2)), parentAnnotation = [Left (Info.FunctionCall, "foo")] } blobs :: Both SourceBlob blobs = both (SourceBlob (fromText "[]") nullOid "a.js" (Just defaultPlainBlob)) (SourceBlob (fromText "[a]") nullOid "b.js" (Just defaultPlainBlob)) @@ -43,7 +46,7 @@ spec :: Spec spec = parallel $ do describe "diffSummaries" $ do it "outputs a diff summary" $ do - diffSummaries blobs testDiff `shouldBe` [ Right $ "Added the \"a\" string" ] + diffSummaries blobs testDiff `shouldBe` [ Right "Added the \"a\" string" ] prop "equal terms produce identity diffs" $ \ a -> let term = defaultFeatureVectorDecorator (category . headF) (toTerm (a :: ArbitraryTerm Text (Record '[Category, Range, SourceSpan]))) in From 39e3a01533b449e0957c604cb312a7d94ed2258a Mon Sep 17 00:00:00 2001 From: joshvera Date: Thu, 6 Oct 2016 15:12:14 -0400 Subject: [PATCH 08/27] Fix up DiffSummarySpec ranges --- src/DiffSummary.hs | 4 ++-- test/DiffSummarySpec.hs | 9 +++++---- 2 files changed, 7 insertions(+), 6 deletions(-) diff --git a/src/DiffSummary.hs b/src/DiffSummary.hs index 991cbd0a8..e7570d519 100644 --- a/src/DiffSummary.hs +++ b/src/DiffSummary.hs @@ -1,6 +1,6 @@ {-# LANGUAGE DataKinds, TypeFamilies, ScopedTypeVariables, DeriveAnyClass #-} -module DiffSummary (diffSummaries, DiffSummary(..), DiffInfo(..), diffToDiffSummaries, isBranchInfo, isErrorSummary, JSONSummary) where +module DiffSummary (diffSummaries, DiffSummary(..), DiffInfo(..), diffToDiffSummaries, isBranchInfo, isErrorSummary, JSONSummary(..)) where import Prologue hiding (intercalate) import Diff @@ -54,7 +54,7 @@ identifiable term = isIdentifiable (unwrap term) term data JSONSummary summary span = JSONSummary { summary :: summary, span :: span } | ErrorSummary { summary :: summary, span :: span } - deriving (ToJSON, Generic) + deriving (ToJSON, Generic, Eq, Show) isErrorSummary :: JSONSummary summary span -> Bool isErrorSummary ErrorSummary{} = True diff --git a/test/DiffSummarySpec.hs b/test/DiffSummarySpec.hs index fe2b59fca..f14152bdb 100644 --- a/test/DiffSummarySpec.hs +++ b/test/DiffSummarySpec.hs @@ -20,15 +20,16 @@ import Term.Arbitrary import Test.Hspec (Spec, describe, it, parallel) import Test.Hspec.Expectations.Pretty import Test.Hspec.QuickCheck +import Data.These sourceSpanBetween :: (Int, Int) -> (Int, Int) -> SourceSpan sourceSpanBetween (s1, e1) (s2, e2) = SourceSpan "" (SourcePos s1 e1) (SourcePos s2 e2) arrayInfo :: Record '[Category, Range, SourceSpan] -arrayInfo = ArrayLiteral .: Range 0 3 .: sourceSpanBetween (1, 1) (1, 4) .: RNil +arrayInfo = ArrayLiteral .: Range 0 3 .: sourceSpanBetween (1, 1) (1, 5) .: RNil literalInfo :: Record '[Category, Range, SourceSpan] -literalInfo = StringLiteral .: Range 1 2 .: sourceSpanBetween (1, 2) (1, 3) .: RNil +literalInfo = StringLiteral .: Range 1 2 .: sourceSpanBetween (1, 2) (1, 4) .: RNil testDiff :: Diff (Syntax Text) (Record '[Category, Range, SourceSpan]) testDiff = free $ Free (pure arrayInfo :< Indexed [ free $ Pure (Insert (cofree $ literalInfo :< Leaf "\"a\"")) ]) @@ -37,7 +38,7 @@ testSummary :: DiffSummary DiffInfo testSummary = DiffSummary { patch = Insert (LeafInfo "string" "a" $ sourceSpanBetween (1,1) (1, 2)), parentAnnotation = [] } replacementSummary :: DiffSummary DiffInfo -replacementSummary = DiffSummary { patch = Replace (LeafInfo "string" "a" $ sourceSpanBetween (1,1) (1, 2)) (LeafInfo "symbol" "b" $ sourceSpanBetween (1,1) (1, 2)), parentAnnotation = [Left (Info.FunctionCall, "foo")] } +replacementSummary = DiffSummary { patch = Replace (LeafInfo "string" "a" $ sourceSpanBetween (1, 2) (1, 4)) (LeafInfo "symbol" "b" $ sourceSpanBetween (1,1) (1, 2)), parentAnnotation = [Left (Info.FunctionCall, "foo")] } blobs :: Both SourceBlob blobs = both (SourceBlob (fromText "[]") nullOid "a.js" (Just defaultPlainBlob)) (SourceBlob (fromText "[a]") nullOid "b.js" (Just defaultPlainBlob)) @@ -46,7 +47,7 @@ spec :: Spec spec = parallel $ do describe "diffSummaries" $ do it "outputs a diff summary" $ do - diffSummaries blobs testDiff `shouldBe` [ Right "Added the \"a\" string" ] + diffSummaries blobs testDiff `shouldBe` [ JSONSummary "Added the \"a\" string" (That $ sourceSpanBetween (1, 2) (1, 4)) ] prop "equal terms produce identity diffs" $ \ a -> let term = defaultFeatureVectorDecorator (category . headF) (toTerm (a :: ArbitraryTerm Text (Record '[Category, Range, SourceSpan]))) in From 0ead2d4be891f6e88e6eba3b0ae87a285bfb9093 Mon Sep 17 00:00:00 2001 From: joshvera Date: Thu, 6 Oct 2016 15:16:44 -0400 Subject: [PATCH 09/27] Change rangeToSourceSpan to start from 1 1 --- src/Diffing.hs | 4 ++-- src/Language/Markdown.hs | 2 +- src/Source.hs | 6 +++--- 3 files changed, 6 insertions(+), 6 deletions(-) diff --git a/src/Diffing.hs b/src/Diffing.hs index 461873770..dc338b29d 100644 --- a/src/Diffing.hs +++ b/src/Diffing.hs @@ -82,8 +82,8 @@ lineByLineParser SourceBlob{..} = pure . cofree . root $ case foldl' annotateLea (leaves, _) -> cofree <$> leaves where lines = actualLines source - root children = (Range 0 (length source) .: Program .: sourceRangeToSpan source (toS path) (Range 0 (length source)) .: RNil) :< Indexed children - leaf charIndex line = (Range charIndex (charIndex + T.length line) .: Program .: sourceRangeToSpan source (toS path) (Range charIndex (charIndex + T.length line)) .: RNil) :< Leaf line + root children = (Range 0 (length source) .: Program .: rangeToSourceSpan source (toS path) (Range 0 (length source)) .: RNil) :< Indexed children + leaf charIndex line = (Range charIndex (charIndex + T.length line) .: Program .: rangeToSourceSpan source (toS path) (Range charIndex (charIndex + T.length line)) .: RNil) :< Leaf line annotateLeaves (accum, charIndex) line = (accum <> [ leaf charIndex (toText line) ] , charIndex + length line) toText = T.pack . Source.toString diff --git a/src/Language/Markdown.hs b/src/Language/Markdown.hs index 1dfab6cd9..3430ed9a1 100644 --- a/src/Language/Markdown.hs +++ b/src/Language/Markdown.hs @@ -12,7 +12,7 @@ import Source import Syntax cmarkParser :: Parser (Syntax Text) (Record '[Range, Category, SourceSpan]) -cmarkParser SourceBlob{..} = pure . toTerm (totalRange source) (sourceRangeToSpan source (toS path) $ totalRange source) $ commonmarkToNode [ optSourcePos, optSafe ] (toText source) +cmarkParser SourceBlob{..} = pure . toTerm (totalRange source) (rangeToSourceSpan source (toS path) $ totalRange source) $ commonmarkToNode [ optSourcePos, optSafe ] (toText source) where toTerm :: Range -> SourceSpan -> Node -> Cofree (Syntax Text) (Record '[Range, Category, SourceSpan]) toTerm within withinSpan (Node position t children) = let diff --git a/src/Source.hs b/src/Source.hs index ae90e71c8..4e5b9a024 100644 --- a/src/Source.hs +++ b/src/Source.hs @@ -99,9 +99,9 @@ sourceSpanToRange source SourceSpan{..} = Range start end (leadingRanges, remainingRanges) = splitAt (line spanStart) (actualLineRanges (totalRange source) source) sumLengths = sum . fmap (\ Range{..} -> end - start) -sourceRangeToSpan :: Source Char -> Text -> Range -> SourceSpan -sourceRangeToSpan source name range@Range{} = SourceSpan name startPos endPos - where startPos = maybe (SourcePos 0 0) (toStartPos 0) (head lineRanges) +rangeToSourceSpan :: Source Char -> Text -> Range -> SourceSpan +rangeToSourceSpan source name range@Range{} = SourceSpan name startPos endPos + where startPos = maybe (SourcePos 1 1) (toStartPos 1) (head lineRanges) endPos = toEndPos (length lineRanges) (last lineRanges) lineRanges = actualLineRanges range source toStartPos line range = SourcePos line (start range) From 15cd4777e65eeb901654840d659958c8e44d8142 Mon Sep 17 00:00:00 2001 From: joshvera Date: Thu, 6 Oct 2016 17:55:54 -0400 Subject: [PATCH 10/27] Add SourceSpans to customize ToJSON output for These SourceSpan SourceSpan --- src/DiffSummary.hs | 17 ++++++++++------- src/Info.hs | 2 +- src/Renderer/Summary.hs | 3 +-- src/SourceSpan.hs | 17 ++++++++++++++++- test/DiffSummarySpec.hs | 2 +- 5 files changed, 29 insertions(+), 12 deletions(-) diff --git a/src/DiffSummary.hs b/src/DiffSummary.hs index e7570d519..f3d7a21fe 100644 --- a/src/DiffSummary.hs +++ b/src/DiffSummary.hs @@ -21,7 +21,7 @@ import Text.PrettyPrint.Leijen.Text ((<+>), squotes, space, string, Doc, punctua import qualified Text.PrettyPrint.Leijen.Text as P import SourceSpan import Source -import Data.Aeson (ToJSON) +import Data.Aeson as A data Annotatable a = Annotatable a | Unannotatable a @@ -73,12 +73,15 @@ data DiffSummary a = DiffSummary { } deriving (Eq, Functor, Show, Generic) -- Returns a list of diff summary texts given two source blobs and a diff. -diffSummaries :: (HasCategory leaf, HasField fields Category, HasField fields Range, HasField fields SourceSpan) => Both SourceBlob -> SyntaxDiff leaf fields -> [JSONSummary Text (These SourceSpan SourceSpan)] +diffSummaries :: (HasCategory leaf, HasField fields Category, HasField fields Range, HasField fields SourceSpan) => + Both SourceBlob -> + SyntaxDiff leaf fields -> + [JSONSummary Text SourceSpans] diffSummaries blobs diff = summaryToTexts =<< diffToDiffSummaries (source <$> blobs) diff -- Takes a 'DiffSummary' and returns a list of summary texts representing the LeafInfos -- in that 'DiffSummary'. -summaryToTexts :: DiffSummary DiffInfo -> [JSONSummary Text (These SourceSpan SourceSpan)] +summaryToTexts :: DiffSummary DiffInfo -> [JSONSummary Text SourceSpans] summaryToTexts DiffSummary{..} = (\jsonSummary -> jsonSummary { summary = show $ summary jsonSummary <+> parentContexts parentAnnotation }) <$> summaries patch @@ -100,25 +103,25 @@ diffToDiffSummaries sources = para $ \diff -> (beforeSource, afterSource) = runJoin sources -- Flattens a patch of diff infos into a list of docs, one for every 'LeafInfo' or `ErrorInfo` it contains. -summaries :: Patch DiffInfo -> [JSONSummary Doc (These SourceSpan SourceSpan)] +summaries :: Patch DiffInfo -> [JSONSummary Doc SourceSpans] summaries = \case p@(Replace i1 i2) -> zipWith (\a b -> JSONSummary { summary = summary (prefixWithPatch p This a) <+> "with" <+> determiner i1 <+> summary b - , span = These (span a) (span b) + , span = SourceSpans $ These (span a) (span b) }) (toLeafInfos i1) (toLeafInfos i2) p@(Insert info) -> prefixWithPatch p That <$> toLeafInfos info p@(Delete info) -> prefixWithPatch p This <$> toLeafInfos info -- Prefixes a given doc with the type of patch it represents. -prefixWithPatch :: Patch DiffInfo -> (SourceSpan -> These SourceSpan SourceSpan) -> JSONSummary Doc SourceSpan -> JSONSummary Doc (These SourceSpan SourceSpan) +prefixWithPatch :: Patch DiffInfo -> (SourceSpan -> These SourceSpan SourceSpan) -> JSONSummary Doc SourceSpan -> JSONSummary Doc SourceSpans prefixWithPatch patch constructor = prefixWithThe (patchToPrefix patch) where prefixWithThe prefix jsonSummary = jsonSummary { summary = prefix <+> determiner' patch <+> summary jsonSummary - , span = constructor (span jsonSummary) + , span = SourceSpans $ constructor (span jsonSummary) } patchToPrefix = \case (Replace _ _) -> "Replaced" diff --git a/src/Info.hs b/src/Info.hs index 7dc38bdde..f456aabcf 100644 --- a/src/Info.hs +++ b/src/Info.hs @@ -1,5 +1,5 @@ {-# LANGUAGE DataKinds, GeneralizedNewtypeDeriving #-} -module Info (Range(..), characterRange, setCharacterRange, Category(..), category, setCategory, Cost(..), cost, setCost, SourceSpan(..), SourcePos(..)) where +module Info (Range(..), characterRange, setCharacterRange, Category(..), category, setCategory, Cost(..), cost, setCost, SourceSpan(..), SourcePos(..), SourceSpans(..)) where import Data.Record import Prologue diff --git a/src/Renderer/Summary.hs b/src/Renderer/Summary.hs index d98089467..cd58b583c 100644 --- a/src/Renderer/Summary.hs +++ b/src/Renderer/Summary.hs @@ -10,7 +10,6 @@ import DiffSummary import Data.Map as Map hiding (null) import Source import SourceSpan -import Data.These import Data.Aeson import Data.List as List @@ -22,6 +21,6 @@ summary blobs diff = SummaryOutput $ Map.fromList [ where changes = if null changes' then mempty else Map.singleton summaryKey (toJSON <$> changes') errors = if null errors' then mempty else Map.singleton summaryKey (toJSON <$> errors') - (errors' :: [JSONSummary Text (These SourceSpan SourceSpan)], changes' :: [JSONSummary Text (These SourceSpan SourceSpan)]) = List.partition isErrorSummary summaries + (errors', changes') = List.partition isErrorSummary summaries summaryKey = toSummaryKey (path <$> blobs) summaries = diffSummaries blobs diff diff --git a/src/SourceSpan.hs b/src/SourceSpan.hs index 1e668bc53..bf0db67da 100644 --- a/src/SourceSpan.hs +++ b/src/SourceSpan.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE DeriveAnyClass #-} +{-# LANGUAGE DeriveAnyClass, GeneralizedNewtypeDeriving #-} -- | -- Source position and span information -- Mostly taken from purescript's SourcePos definition. @@ -9,6 +9,7 @@ import Prologue import Data.Aeson ((.=), (.:)) import qualified Data.Aeson as A import Test.QuickCheck +import Data.These import Data.Text.Arbitrary() -- | @@ -74,6 +75,20 @@ instance A.FromJSON SourceSpan where o .: "start" <*> o .: "end" + +newtype SourceSpans = SourceSpans { unSourceSpans :: These SourceSpan SourceSpan } + deriving (Eq, Show) + +instance A.ToJSON SourceSpans where + toJSON (SourceSpans spans) = case spans of + (This span) -> A.object ["this" .= span] + (That span) -> A.object ["that" .= span] + (These span1 span2) -> A.object ["these" .= (span1, span2)] + toEncoding (SourceSpans spans) = case spans of + (This span) -> A.pairs $ "this" .= span + (That span) -> A.pairs $ "that" .= span + (These span1 span2) -> A.pairs $ "these" .= (span1, span2) + instance Arbitrary SourcePos where arbitrary = SourcePos <$> arbitrary <*> arbitrary shrink = genericShrink diff --git a/test/DiffSummarySpec.hs b/test/DiffSummarySpec.hs index f14152bdb..9eeaec446 100644 --- a/test/DiffSummarySpec.hs +++ b/test/DiffSummarySpec.hs @@ -47,7 +47,7 @@ spec :: Spec spec = parallel $ do describe "diffSummaries" $ do it "outputs a diff summary" $ do - diffSummaries blobs testDiff `shouldBe` [ JSONSummary "Added the \"a\" string" (That $ sourceSpanBetween (1, 2) (1, 4)) ] + diffSummaries blobs testDiff `shouldBe` [ JSONSummary "Added the \"a\" string" (SourceSpans . That $ sourceSpanBetween (1, 2) (1, 4)) ] prop "equal terms produce identity diffs" $ \ a -> let term = defaultFeatureVectorDecorator (category . headF) (toTerm (a :: ArbitraryTerm Text (Record '[Category, Range, SourceSpan]))) in From 4c219279b2b675b0062973d4d0fff0f44a19b195 Mon Sep 17 00:00:00 2001 From: joshvera Date: Thu, 6 Oct 2016 18:31:06 -0400 Subject: [PATCH 11/27] SourceSpans are one-indexed --- src/TreeSitter.hs | 6 ++++-- 1 file changed, 4 insertions(+), 2 deletions(-) diff --git a/src/TreeSitter.hs b/src/TreeSitter.hs index b1c251ab9..7ca9ca8f0 100644 --- a/src/TreeSitter.hs +++ b/src/TreeSitter.hs @@ -43,10 +43,12 @@ documentToTerm language document SourceBlob{..} = alloca $ \ root -> do let range = Range { start = fromIntegral $ ts_node_p_start_char node, end = fromIntegral $ ts_node_p_end_char node } + let startPos = SourcePos (1 + (fromIntegral $! ts_node_p_start_point_row node)) (1 + (fromIntegral $! ts_node_p_start_point_column node)) + let endPos = SourcePos (1 + (fromIntegral $! ts_node_p_end_point_row node)) (1 + (fromIntegral $! ts_node_p_end_point_column node)) let sourceSpan = SourceSpan { spanName = toS path - , spanStart = SourcePos (fromIntegral $! ts_node_p_start_point_row node) (fromIntegral $! ts_node_p_start_point_column node) - , spanEnd = SourcePos (fromIntegral $! ts_node_p_end_point_row node) (fromIntegral $! ts_node_p_end_point_column node) + , spanStart = startPos + , spanEnd = endPos } -- Note: The strict application here is semantically important. From b9cf07f2649c14a33f85bbcb3a481fa5bb25dc6f Mon Sep 17 00:00:00 2001 From: joshvera Date: Thu, 6 Oct 2016 18:36:49 -0400 Subject: [PATCH 12/27] I guess DeriveAnyClass subsumes GeneralizedNewtypeDeriving --- src/SourceSpan.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/SourceSpan.hs b/src/SourceSpan.hs index bf0db67da..112191eba 100644 --- a/src/SourceSpan.hs +++ b/src/SourceSpan.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE DeriveAnyClass, GeneralizedNewtypeDeriving #-} +{-# LANGUAGE DeriveAnyClass #-} -- | -- Source position and span information -- Mostly taken from purescript's SourcePos definition. From f7e0cb53ddc956abb5b28d510af9700607f15971 Mon Sep 17 00:00:00 2001 From: joshvera Date: Fri, 7 Oct 2016 11:29:44 -0400 Subject: [PATCH 13/27] ++javascript --- test/corpus/repos/javascript | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/test/corpus/repos/javascript b/test/corpus/repos/javascript index 14310ea87..946dc2ba4 160000 --- a/test/corpus/repos/javascript +++ b/test/corpus/repos/javascript @@ -1 +1 @@ -Subproject commit 14310ea870b177f2187e152498699c8cd1b039f3 +Subproject commit 946dc2ba4cf404c4d8e3ca7a23c09e2b14f3e06b From 624918b113661eaddfbdc0dc946be484cbae39a8 Mon Sep 17 00:00:00 2001 From: joshvera Date: Tue, 11 Oct 2016 11:10:16 -0400 Subject: [PATCH 14/27] remove files --- .../javascript/anonymous-function.json | 488 -------------- .../anonymous-parameterless-function.json | 308 --------- .../diff-summaries/javascript/array.json | 282 -------- .../javascript/arrow-function.json | 308 --------- .../diff-summaries/javascript/assignment.json | 308 --------- .../javascript/bitwise-operator.json | 308 --------- .../javascript/boolean-operator.json | 208 ------ .../javascript/chained-callbacks.json | 428 ------------ .../javascript/chained-property-access.json | 368 ----------- .../diff-summaries/javascript/class.json | 428 ------------ .../javascript/comma-operator.json | 418 ------------ .../diff-summaries/javascript/comment.json | 308 --------- .../javascript/constructor-call.json | 308 --------- .../javascript/delete-operator.json | 308 --------- .../javascript/do-while-statement.json | 368 ----------- .../diff-summaries/javascript/export.json | 267 -------- .../diff-summaries/javascript/false.json | 316 --------- .../javascript/for-in-statement.json | 428 ------------ .../for-loop-with-in-statement.json | 368 ----------- .../javascript/for-of-statement.json | 428 ------------ .../javascript/for-statement.json | 308 --------- .../javascript/function-call-args.json | 608 ------------------ .../javascript/function-call.json | 308 --------- .../diff-summaries/javascript/function.json | 308 --------- .../javascript/generator-function.json | 308 --------- .../diff-summaries/javascript/identifier.json | 308 --------- .../diff-summaries/javascript/if-else.json | 308 --------- test/corpus/diff-summaries/javascript/if.json | 308 --------- .../diff-summaries/javascript/import.json | 214 ------ .../javascript/math-assignment-operator.json | 308 --------- .../javascript/math-operator.json | 368 ----------- .../javascript/member-access-assignment.json | 308 --------- .../javascript/member-access.json | 308 --------- .../javascript/method-call.json | 308 --------- .../javascript/named-function.json | 444 ------------- .../nested-do-while-in-function.json | 368 ----------- .../javascript/nested-functions.json | 368 ----------- .../diff-summaries/javascript/null.json | 316 --------- .../diff-summaries/javascript/number.json | 308 --------- .../javascript/object-with-methods.json | 308 --------- .../diff-summaries/javascript/object.json | 316 --------- .../diff-summaries/javascript/regex.json | 308 --------- .../javascript/relational-operator.json | 208 ------ .../javascript/return-statement.json | 282 -------- .../diff-summaries/javascript/string.json | 308 --------- .../subscript-access-assignment.json | 308 --------- .../javascript/subscript-access-string.json | 308 --------- .../javascript/subscript-access-variable.json | 308 --------- .../javascript/switch-statement.json | 368 ----------- .../javascript/template-string.json | 308 --------- .../diff-summaries/javascript/ternary.json | 316 --------- .../javascript/this-expression.json | 316 --------- .../javascript/throw-statement.json | 308 --------- .../diff-summaries/javascript/true.json | 316 --------- .../javascript/try-statement.json | 368 ----------- .../javascript/type-operator.json | 282 -------- .../diff-summaries/javascript/undefined.json | 316 --------- .../javascript/var-declaration.json | 512 --------------- .../diff-summaries/javascript/variable.json | 308 --------- .../javascript/void-operator.json | 308 --------- .../javascript/while-statement.json | 368 ----------- 61 files changed, 20381 deletions(-) delete mode 100644 test/corpus/diff-summaries/javascript/anonymous-function.json delete mode 100644 test/corpus/diff-summaries/javascript/anonymous-parameterless-function.json delete mode 100644 test/corpus/diff-summaries/javascript/array.json delete mode 100644 test/corpus/diff-summaries/javascript/arrow-function.json delete mode 100644 test/corpus/diff-summaries/javascript/assignment.json delete mode 100644 test/corpus/diff-summaries/javascript/bitwise-operator.json delete mode 100644 test/corpus/diff-summaries/javascript/boolean-operator.json delete mode 100644 test/corpus/diff-summaries/javascript/chained-callbacks.json delete mode 100644 test/corpus/diff-summaries/javascript/chained-property-access.json delete mode 100644 test/corpus/diff-summaries/javascript/class.json delete mode 100644 test/corpus/diff-summaries/javascript/comma-operator.json delete mode 100644 test/corpus/diff-summaries/javascript/comment.json delete mode 100644 test/corpus/diff-summaries/javascript/constructor-call.json delete mode 100644 test/corpus/diff-summaries/javascript/delete-operator.json delete mode 100644 test/corpus/diff-summaries/javascript/do-while-statement.json delete mode 100644 test/corpus/diff-summaries/javascript/export.json delete mode 100644 test/corpus/diff-summaries/javascript/false.json delete mode 100644 test/corpus/diff-summaries/javascript/for-in-statement.json delete mode 100644 test/corpus/diff-summaries/javascript/for-loop-with-in-statement.json delete mode 100644 test/corpus/diff-summaries/javascript/for-of-statement.json delete mode 100644 test/corpus/diff-summaries/javascript/for-statement.json delete mode 100644 test/corpus/diff-summaries/javascript/function-call-args.json delete mode 100644 test/corpus/diff-summaries/javascript/function-call.json delete mode 100644 test/corpus/diff-summaries/javascript/function.json delete mode 100644 test/corpus/diff-summaries/javascript/generator-function.json delete mode 100644 test/corpus/diff-summaries/javascript/identifier.json delete mode 100644 test/corpus/diff-summaries/javascript/if-else.json delete mode 100644 test/corpus/diff-summaries/javascript/if.json delete mode 100644 test/corpus/diff-summaries/javascript/import.json delete mode 100644 test/corpus/diff-summaries/javascript/math-assignment-operator.json delete mode 100644 test/corpus/diff-summaries/javascript/math-operator.json delete mode 100644 test/corpus/diff-summaries/javascript/member-access-assignment.json delete mode 100644 test/corpus/diff-summaries/javascript/member-access.json delete mode 100644 test/corpus/diff-summaries/javascript/method-call.json delete mode 100644 test/corpus/diff-summaries/javascript/named-function.json delete mode 100644 test/corpus/diff-summaries/javascript/nested-do-while-in-function.json delete mode 100644 test/corpus/diff-summaries/javascript/nested-functions.json delete mode 100644 test/corpus/diff-summaries/javascript/null.json delete mode 100644 test/corpus/diff-summaries/javascript/number.json delete mode 100644 test/corpus/diff-summaries/javascript/object-with-methods.json delete mode 100644 test/corpus/diff-summaries/javascript/object.json delete mode 100644 test/corpus/diff-summaries/javascript/regex.json delete mode 100644 test/corpus/diff-summaries/javascript/relational-operator.json delete mode 100644 test/corpus/diff-summaries/javascript/return-statement.json delete mode 100644 test/corpus/diff-summaries/javascript/string.json delete mode 100644 test/corpus/diff-summaries/javascript/subscript-access-assignment.json delete mode 100644 test/corpus/diff-summaries/javascript/subscript-access-string.json delete mode 100644 test/corpus/diff-summaries/javascript/subscript-access-variable.json delete mode 100644 test/corpus/diff-summaries/javascript/switch-statement.json delete mode 100644 test/corpus/diff-summaries/javascript/template-string.json delete mode 100644 test/corpus/diff-summaries/javascript/ternary.json delete mode 100644 test/corpus/diff-summaries/javascript/this-expression.json delete mode 100644 test/corpus/diff-summaries/javascript/throw-statement.json delete mode 100644 test/corpus/diff-summaries/javascript/true.json delete mode 100644 test/corpus/diff-summaries/javascript/try-statement.json delete mode 100644 test/corpus/diff-summaries/javascript/type-operator.json delete mode 100644 test/corpus/diff-summaries/javascript/undefined.json delete mode 100644 test/corpus/diff-summaries/javascript/var-declaration.json delete mode 100644 test/corpus/diff-summaries/javascript/variable.json delete mode 100644 test/corpus/diff-summaries/javascript/void-operator.json delete mode 100644 test/corpus/diff-summaries/javascript/while-statement.json diff --git a/test/corpus/diff-summaries/javascript/anonymous-function.json b/test/corpus/diff-summaries/javascript/anonymous-function.json deleted file mode 100644 index 300e1601a..000000000 --- a/test/corpus/diff-summaries/javascript/anonymous-function.json +++ /dev/null @@ -1,488 +0,0 @@ -[{ - "testCaseDescription": "javascript-anonymous-function-insert-test", - "expectedResult": { - "changes": { - "anonymous-function.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "anonymous-function.js", - "end": [ - 1, - 32 - ] - } - }, - "summary": "Added an anonymous(a, b) function", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "anonymous-function.js" - ], - "sha1": "4e616c4976a8cc24c20fda3c6bfcde4cfa22483f", - "gitDir": "test/corpus/repos/javascript", - "sha2": "11adb5f79753721a4cb9dd4c953f9baa21da78e4" -} -,{ - "testCaseDescription": "javascript-anonymous-function-replacement-insert-test", - "expectedResult": { - "changes": { - "anonymous-function.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "anonymous-function.js", - "end": [ - 1, - 32 - ] - } - }, - "summary": "Added an anonymous(b, c) function", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "anonymous-function.js", - "end": [ - 2, - 32 - ] - } - }, - "summary": "Added an anonymous(a, b) function", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "anonymous-function.js" - ], - "sha1": "11adb5f79753721a4cb9dd4c953f9baa21da78e4", - "gitDir": "test/corpus/repos/javascript", - "sha2": "22aa5c90ae1f387ad7f6fd2169bb97f5d3c57446" -} -,{ - "testCaseDescription": "javascript-anonymous-function-delete-insert-test", - "expectedResult": { - "changes": { - "anonymous-function.js": [ - { - "span": { - "these": [ - { - "start": [ - 1, - 10 - ], - "name": "anonymous-function.js", - "end": [ - 1, - 11 - ] - }, - { - "start": [ - 1, - 10 - ], - "name": "anonymous-function.js", - "end": [ - 1, - 11 - ] - } - ] - }, - "summary": "Replaced the 'b' identifier with the 'a' identifier", - "tag": "JSONSummary" - }, - { - "span": { - "these": [ - { - "start": [ - 1, - 12 - ], - "name": "anonymous-function.js", - "end": [ - 1, - 13 - ] - }, - { - "start": [ - 1, - 12 - ], - "name": "anonymous-function.js", - "end": [ - 1, - 13 - ] - } - ] - }, - "summary": "Replaced the 'c' identifier with the 'b' identifier", - "tag": "JSONSummary" - }, - { - "span": { - "these": [ - { - "start": [ - 1, - 24 - ], - "name": "anonymous-function.js", - "end": [ - 1, - 25 - ] - }, - { - "start": [ - 1, - 24 - ], - "name": "anonymous-function.js", - "end": [ - 1, - 25 - ] - } - ] - }, - "summary": "Replaced the 'b' identifier with the 'a' identifier", - "tag": "JSONSummary" - }, - { - "span": { - "these": [ - { - "start": [ - 1, - 28 - ], - "name": "anonymous-function.js", - "end": [ - 1, - 29 - ] - }, - { - "start": [ - 1, - 28 - ], - "name": "anonymous-function.js", - "end": [ - 1, - 29 - ] - } - ] - }, - "summary": "Replaced the 'c' identifier with the 'b' identifier", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "anonymous-function.js" - ], - "sha1": "22aa5c90ae1f387ad7f6fd2169bb97f5d3c57446", - "gitDir": "test/corpus/repos/javascript", - "sha2": "00641b36f04df3262046fb678d56334975197898" -} -,{ - "testCaseDescription": "javascript-anonymous-function-replacement-test", - "expectedResult": { - "changes": { - "anonymous-function.js": [ - { - "span": { - "these": [ - { - "start": [ - 1, - 10 - ], - "name": "anonymous-function.js", - "end": [ - 1, - 11 - ] - }, - { - "start": [ - 1, - 10 - ], - "name": "anonymous-function.js", - "end": [ - 1, - 11 - ] - } - ] - }, - "summary": "Replaced the 'a' identifier with the 'b' identifier", - "tag": "JSONSummary" - }, - { - "span": { - "these": [ - { - "start": [ - 1, - 12 - ], - "name": "anonymous-function.js", - "end": [ - 1, - 13 - ] - }, - { - "start": [ - 1, - 12 - ], - "name": "anonymous-function.js", - "end": [ - 1, - 13 - ] - } - ] - }, - "summary": "Replaced the 'b' identifier with the 'c' identifier", - "tag": "JSONSummary" - }, - { - "span": { - "these": [ - { - "start": [ - 1, - 24 - ], - "name": "anonymous-function.js", - "end": [ - 1, - 25 - ] - }, - { - "start": [ - 1, - 24 - ], - "name": "anonymous-function.js", - "end": [ - 1, - 25 - ] - } - ] - }, - "summary": "Replaced the 'a' identifier with the 'b' identifier", - "tag": "JSONSummary" - }, - { - "span": { - "these": [ - { - "start": [ - 1, - 28 - ], - "name": "anonymous-function.js", - "end": [ - 1, - 29 - ] - }, - { - "start": [ - 1, - 28 - ], - "name": "anonymous-function.js", - "end": [ - 1, - 29 - ] - } - ] - }, - "summary": "Replaced the 'b' identifier with the 'c' identifier", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "anonymous-function.js" - ], - "sha1": "00641b36f04df3262046fb678d56334975197898", - "gitDir": "test/corpus/repos/javascript", - "sha2": "5005a8366ec0cd60cb0d36c5b8e70573ab05b5e2" -} -,{ - "testCaseDescription": "javascript-anonymous-function-delete-replacement-test", - "expectedResult": { - "changes": { - "anonymous-function.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "anonymous-function.js", - "end": [ - 1, - 32 - ] - } - }, - "summary": "Deleted an anonymous(b, c) function", - "tag": "JSONSummary" - }, - { - "span": { - "this": { - "start": [ - 2, - 1 - ], - "name": "anonymous-function.js", - "end": [ - 2, - 32 - ] - } - }, - "summary": "Deleted an anonymous(a, b) function", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "anonymous-function.js", - "end": [ - 2, - 32 - ] - } - }, - "summary": "Added an anonymous(b, c) function", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "anonymous-function.js" - ], - "sha1": "5005a8366ec0cd60cb0d36c5b8e70573ab05b5e2", - "gitDir": "test/corpus/repos/javascript", - "sha2": "1356b34dcce5152406f29f015d8342982a3704e4" -} -,{ - "testCaseDescription": "javascript-anonymous-function-delete-test", - "expectedResult": { - "changes": { - "anonymous-function.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "anonymous-function.js", - "end": [ - 1, - 32 - ] - } - }, - "summary": "Deleted an anonymous(a, b) function", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "anonymous-function.js" - ], - "sha1": "1356b34dcce5152406f29f015d8342982a3704e4", - "gitDir": "test/corpus/repos/javascript", - "sha2": "22d5b6e950763c553f1efb105400c69ab6f34b31" -} -,{ - "testCaseDescription": "javascript-anonymous-function-delete-rest-test", - "expectedResult": { - "changes": { - "anonymous-function.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "anonymous-function.js", - "end": [ - 1, - 32 - ] - } - }, - "summary": "Deleted an anonymous(b, c) function", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "anonymous-function.js" - ], - "sha1": "22d5b6e950763c553f1efb105400c69ab6f34b31", - "gitDir": "test/corpus/repos/javascript", - "sha2": "d03e64156e1eccacaee03b2180ecdeba6ca0385c" -}] diff --git a/test/corpus/diff-summaries/javascript/anonymous-parameterless-function.json b/test/corpus/diff-summaries/javascript/anonymous-parameterless-function.json deleted file mode 100644 index 2f4388594..000000000 --- a/test/corpus/diff-summaries/javascript/anonymous-parameterless-function.json +++ /dev/null @@ -1,308 +0,0 @@ -[{ - "testCaseDescription": "javascript-anonymous-parameterless-function-insert-test", - "expectedResult": { - "changes": { - "anonymous-parameterless-function.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "anonymous-parameterless-function.js", - "end": [ - 1, - 28 - ] - } - }, - "summary": "Added an anonymous() function", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "anonymous-parameterless-function.js" - ], - "sha1": "d03e64156e1eccacaee03b2180ecdeba6ca0385c", - "gitDir": "test/corpus/repos/javascript", - "sha2": "74ca1b76b63e514abaf450801b7c266a075d88cf" -} -,{ - "testCaseDescription": "javascript-anonymous-parameterless-function-replacement-insert-test", - "expectedResult": { - "changes": { - "anonymous-parameterless-function.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "anonymous-parameterless-function.js", - "end": [ - 1, - 31 - ] - } - }, - "summary": "Added an anonymous() function", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "anonymous-parameterless-function.js", - "end": [ - 2, - 28 - ] - } - }, - "summary": "Added an anonymous() function", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "anonymous-parameterless-function.js" - ], - "sha1": "74ca1b76b63e514abaf450801b7c266a075d88cf", - "gitDir": "test/corpus/repos/javascript", - "sha2": "dbe1defa8484a6fe83354587d0c2d694d53d85d7" -} -,{ - "testCaseDescription": "javascript-anonymous-parameterless-function-delete-insert-test", - "expectedResult": { - "changes": { - "anonymous-parameterless-function.js": [ - { - "span": { - "these": [ - { - "start": [ - 1, - 21 - ], - "name": "anonymous-parameterless-function.js", - "end": [ - 1, - 28 - ] - }, - { - "start": [ - 1, - 21 - ], - "name": "anonymous-parameterless-function.js", - "end": [ - 1, - 25 - ] - } - ] - }, - "summary": "Replaced the 'hello' string with the 'hi' string", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "anonymous-parameterless-function.js" - ], - "sha1": "dbe1defa8484a6fe83354587d0c2d694d53d85d7", - "gitDir": "test/corpus/repos/javascript", - "sha2": "ebe1b4c63b69969ba5879d11d968a450a4764320" -} -,{ - "testCaseDescription": "javascript-anonymous-parameterless-function-replacement-test", - "expectedResult": { - "changes": { - "anonymous-parameterless-function.js": [ - { - "span": { - "these": [ - { - "start": [ - 1, - 21 - ], - "name": "anonymous-parameterless-function.js", - "end": [ - 1, - 25 - ] - }, - { - "start": [ - 1, - 21 - ], - "name": "anonymous-parameterless-function.js", - "end": [ - 1, - 28 - ] - } - ] - }, - "summary": "Replaced the 'hi' string with the 'hello' string", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "anonymous-parameterless-function.js" - ], - "sha1": "ebe1b4c63b69969ba5879d11d968a450a4764320", - "gitDir": "test/corpus/repos/javascript", - "sha2": "2f5c02d12967641470fcd29a06d32300cecc578b" -} -,{ - "testCaseDescription": "javascript-anonymous-parameterless-function-delete-replacement-test", - "expectedResult": { - "changes": { - "anonymous-parameterless-function.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "anonymous-parameterless-function.js", - "end": [ - 1, - 31 - ] - } - }, - "summary": "Deleted an anonymous() function", - "tag": "JSONSummary" - }, - { - "span": { - "this": { - "start": [ - 2, - 1 - ], - "name": "anonymous-parameterless-function.js", - "end": [ - 2, - 28 - ] - } - }, - "summary": "Deleted an anonymous() function", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "anonymous-parameterless-function.js", - "end": [ - 2, - 31 - ] - } - }, - "summary": "Added an anonymous() function", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "anonymous-parameterless-function.js" - ], - "sha1": "2f5c02d12967641470fcd29a06d32300cecc578b", - "gitDir": "test/corpus/repos/javascript", - "sha2": "07dbb53e127cb5de0e07c6f449d2959038088696" -} -,{ - "testCaseDescription": "javascript-anonymous-parameterless-function-delete-test", - "expectedResult": { - "changes": { - "anonymous-parameterless-function.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "anonymous-parameterless-function.js", - "end": [ - 1, - 28 - ] - } - }, - "summary": "Deleted an anonymous() function", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "anonymous-parameterless-function.js" - ], - "sha1": "07dbb53e127cb5de0e07c6f449d2959038088696", - "gitDir": "test/corpus/repos/javascript", - "sha2": "4d244392442a153a1495219111c1fa2929fae4ac" -} -,{ - "testCaseDescription": "javascript-anonymous-parameterless-function-delete-rest-test", - "expectedResult": { - "changes": { - "anonymous-parameterless-function.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "anonymous-parameterless-function.js", - "end": [ - 1, - 31 - ] - } - }, - "summary": "Deleted an anonymous() function", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "anonymous-parameterless-function.js" - ], - "sha1": "4d244392442a153a1495219111c1fa2929fae4ac", - "gitDir": "test/corpus/repos/javascript", - "sha2": "59872fcdcee9cd22104933bbc925d9987cd393b6" -}] diff --git a/test/corpus/diff-summaries/javascript/array.json b/test/corpus/diff-summaries/javascript/array.json deleted file mode 100644 index 2dcd6534c..000000000 --- a/test/corpus/diff-summaries/javascript/array.json +++ /dev/null @@ -1,282 +0,0 @@ -[{ - "testCaseDescription": "javascript-array-insert-test", - "expectedResult": { - "changes": { - "array.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "array.js", - "end": [ - 1, - 12 - ] - } - }, - "summary": "Added the '[ \"item1\" ]' array", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "array.js" - ], - "sha1": "72a672d52b6952c146edab2927b3b05abd022921", - "gitDir": "test/corpus/repos/javascript", - "sha2": "8a68989a0d6ab0cd555a73289acaf3ee5100c31d" -} -,{ - "testCaseDescription": "javascript-array-replacement-insert-test", - "expectedResult": { - "changes": { - "array.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "array.js", - "end": [ - 1, - 21 - ] - } - }, - "summary": "Added the '[ \"item1\", \"item2\" ]' array", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "array.js", - "end": [ - 2, - 12 - ] - } - }, - "summary": "Added the '[ \"item1\" ]' array", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "array.js" - ], - "sha1": "8a68989a0d6ab0cd555a73289acaf3ee5100c31d", - "gitDir": "test/corpus/repos/javascript", - "sha2": "aba697e2f9d98d3f14f31cfe741d1c0150c3a99a" -} -,{ - "testCaseDescription": "javascript-array-delete-insert-test", - "expectedResult": { - "changes": { - "array.js": [ - { - "span": { - "this": { - "start": [ - 1, - 12 - ], - "name": "array.js", - "end": [ - 1, - 19 - ] - } - }, - "summary": "Deleted the \"item2\" string", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "array.js" - ], - "sha1": "aba697e2f9d98d3f14f31cfe741d1c0150c3a99a", - "gitDir": "test/corpus/repos/javascript", - "sha2": "7616278362cc2f6254d943d75632c5235bba9971" -} -,{ - "testCaseDescription": "javascript-array-replacement-test", - "expectedResult": { - "changes": { - "array.js": [ - { - "span": { - "that": { - "start": [ - 1, - 12 - ], - "name": "array.js", - "end": [ - 1, - 19 - ] - } - }, - "summary": "Added the \"item2\" string", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "array.js" - ], - "sha1": "7616278362cc2f6254d943d75632c5235bba9971", - "gitDir": "test/corpus/repos/javascript", - "sha2": "44749342699a37f8ef292b98a3982097a3d08011" -} -,{ - "testCaseDescription": "javascript-array-delete-replacement-test", - "expectedResult": { - "changes": { - "array.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "array.js", - "end": [ - 1, - 21 - ] - } - }, - "summary": "Deleted the '[ \"item1\", \"item2\" ]' array", - "tag": "JSONSummary" - }, - { - "span": { - "this": { - "start": [ - 2, - 1 - ], - "name": "array.js", - "end": [ - 2, - 12 - ] - } - }, - "summary": "Deleted the '[ \"item1\" ]' array", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "array.js", - "end": [ - 2, - 21 - ] - } - }, - "summary": "Added the '[ \"item1\", \"item2\" ]' array", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "array.js" - ], - "sha1": "44749342699a37f8ef292b98a3982097a3d08011", - "gitDir": "test/corpus/repos/javascript", - "sha2": "fe6708bd26fdab5406160bac05f1cff56de363f9" -} -,{ - "testCaseDescription": "javascript-array-delete-test", - "expectedResult": { - "changes": { - "array.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "array.js", - "end": [ - 1, - 12 - ] - } - }, - "summary": "Deleted the '[ \"item1\" ]' array", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "array.js" - ], - "sha1": "fe6708bd26fdab5406160bac05f1cff56de363f9", - "gitDir": "test/corpus/repos/javascript", - "sha2": "1e7aa51504a3eb084aaca63663658690ce3f65f0" -} -,{ - "testCaseDescription": "javascript-array-delete-rest-test", - "expectedResult": { - "changes": { - "array.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "array.js", - "end": [ - 1, - 21 - ] - } - }, - "summary": "Deleted the '[ \"item1\", \"item2\" ]' array", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "array.js" - ], - "sha1": "1e7aa51504a3eb084aaca63663658690ce3f65f0", - "gitDir": "test/corpus/repos/javascript", - "sha2": "492ece78ac243f74d0f0bfce83c94b7162c1eaa6" -}] diff --git a/test/corpus/diff-summaries/javascript/arrow-function.json b/test/corpus/diff-summaries/javascript/arrow-function.json deleted file mode 100644 index 4d6192573..000000000 --- a/test/corpus/diff-summaries/javascript/arrow-function.json +++ /dev/null @@ -1,308 +0,0 @@ -[{ - "testCaseDescription": "javascript-arrow-function-insert-test", - "expectedResult": { - "changes": { - "arrow-function.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "arrow-function.js", - "end": [ - 1, - 24 - ] - } - }, - "summary": "Added an anonymous(f, g) function", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "arrow-function.js" - ], - "sha1": "142158e6e72a9a884b0d89c0b044b5c1473248db", - "gitDir": "test/corpus/repos/javascript", - "sha2": "13ec03f9e751e39a9264ab096a2340c206e46e94" -} -,{ - "testCaseDescription": "javascript-arrow-function-replacement-insert-test", - "expectedResult": { - "changes": { - "arrow-function.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "arrow-function.js", - "end": [ - 1, - 24 - ] - } - }, - "summary": "Added an anonymous(f, g) function", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "arrow-function.js", - "end": [ - 2, - 24 - ] - } - }, - "summary": "Added an anonymous(f, g) function", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "arrow-function.js" - ], - "sha1": "13ec03f9e751e39a9264ab096a2340c206e46e94", - "gitDir": "test/corpus/repos/javascript", - "sha2": "5bed5bece02a8f7e16801c1e44d6b73af832e316" -} -,{ - "testCaseDescription": "javascript-arrow-function-delete-insert-test", - "expectedResult": { - "changes": { - "arrow-function.js": [ - { - "span": { - "these": [ - { - "start": [ - 1, - 20 - ], - "name": "arrow-function.js", - "end": [ - 1, - 21 - ] - }, - { - "start": [ - 1, - 20 - ], - "name": "arrow-function.js", - "end": [ - 1, - 21 - ] - } - ] - }, - "summary": "Replaced the 'g' identifier with the 'h' identifier", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "arrow-function.js" - ], - "sha1": "5bed5bece02a8f7e16801c1e44d6b73af832e316", - "gitDir": "test/corpus/repos/javascript", - "sha2": "93d231ad655a0f193a27b6aed6e5daee14efb962" -} -,{ - "testCaseDescription": "javascript-arrow-function-replacement-test", - "expectedResult": { - "changes": { - "arrow-function.js": [ - { - "span": { - "these": [ - { - "start": [ - 1, - 20 - ], - "name": "arrow-function.js", - "end": [ - 1, - 21 - ] - }, - { - "start": [ - 1, - 20 - ], - "name": "arrow-function.js", - "end": [ - 1, - 21 - ] - } - ] - }, - "summary": "Replaced the 'h' identifier with the 'g' identifier", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "arrow-function.js" - ], - "sha1": "93d231ad655a0f193a27b6aed6e5daee14efb962", - "gitDir": "test/corpus/repos/javascript", - "sha2": "bdf1809e96da6408d7fe4992cf0cb8b2617c283b" -} -,{ - "testCaseDescription": "javascript-arrow-function-delete-replacement-test", - "expectedResult": { - "changes": { - "arrow-function.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "arrow-function.js", - "end": [ - 1, - 24 - ] - } - }, - "summary": "Deleted an anonymous(f, g) function", - "tag": "JSONSummary" - }, - { - "span": { - "this": { - "start": [ - 2, - 1 - ], - "name": "arrow-function.js", - "end": [ - 2, - 24 - ] - } - }, - "summary": "Deleted an anonymous(f, g) function", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "arrow-function.js", - "end": [ - 2, - 24 - ] - } - }, - "summary": "Added an anonymous(f, g) function", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "arrow-function.js" - ], - "sha1": "bdf1809e96da6408d7fe4992cf0cb8b2617c283b", - "gitDir": "test/corpus/repos/javascript", - "sha2": "47663edfd71e7dca4832c0c6981e05116a2ed347" -} -,{ - "testCaseDescription": "javascript-arrow-function-delete-test", - "expectedResult": { - "changes": { - "arrow-function.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "arrow-function.js", - "end": [ - 1, - 24 - ] - } - }, - "summary": "Deleted an anonymous(f, g) function", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "arrow-function.js" - ], - "sha1": "47663edfd71e7dca4832c0c6981e05116a2ed347", - "gitDir": "test/corpus/repos/javascript", - "sha2": "89d1bae5033feb4a97fe91084db2a9b2faa48239" -} -,{ - "testCaseDescription": "javascript-arrow-function-delete-rest-test", - "expectedResult": { - "changes": { - "arrow-function.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "arrow-function.js", - "end": [ - 1, - 24 - ] - } - }, - "summary": "Deleted an anonymous(f, g) function", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "arrow-function.js" - ], - "sha1": "89d1bae5033feb4a97fe91084db2a9b2faa48239", - "gitDir": "test/corpus/repos/javascript", - "sha2": "304e0c432994c642daa18c284f4c1578416e77e1" -}] diff --git a/test/corpus/diff-summaries/javascript/assignment.json b/test/corpus/diff-summaries/javascript/assignment.json deleted file mode 100644 index 871c9ab87..000000000 --- a/test/corpus/diff-summaries/javascript/assignment.json +++ /dev/null @@ -1,308 +0,0 @@ -[{ - "testCaseDescription": "javascript-assignment-insert-test", - "expectedResult": { - "changes": { - "assignment.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "assignment.js", - "end": [ - 1, - 6 - ] - } - }, - "summary": "Added the 'x' assignment", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "assignment.js" - ], - "sha1": "e66aa2b6bacc2bbd796427540227b298518b1389", - "gitDir": "test/corpus/repos/javascript", - "sha2": "3956fb4eec4f0bd0a62f4e0b55ccaf0125576854" -} -,{ - "testCaseDescription": "javascript-assignment-replacement-insert-test", - "expectedResult": { - "changes": { - "assignment.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "assignment.js", - "end": [ - 1, - 6 - ] - } - }, - "summary": "Added the 'x' assignment", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "assignment.js", - "end": [ - 2, - 6 - ] - } - }, - "summary": "Added the 'x' assignment", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "assignment.js" - ], - "sha1": "3956fb4eec4f0bd0a62f4e0b55ccaf0125576854", - "gitDir": "test/corpus/repos/javascript", - "sha2": "d1726bb6040b8c5f6358f7d1af2ebc11e7d96e9f" -} -,{ - "testCaseDescription": "javascript-assignment-delete-insert-test", - "expectedResult": { - "changes": { - "assignment.js": [ - { - "span": { - "these": [ - { - "start": [ - 1, - 5 - ], - "name": "assignment.js", - "end": [ - 1, - 6 - ] - }, - { - "start": [ - 1, - 5 - ], - "name": "assignment.js", - "end": [ - 1, - 6 - ] - } - ] - }, - "summary": "Replaced '1' with '0' in an assignment to x", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "assignment.js" - ], - "sha1": "d1726bb6040b8c5f6358f7d1af2ebc11e7d96e9f", - "gitDir": "test/corpus/repos/javascript", - "sha2": "01f04fbd4037191df6536ca1d542eb8f2678082d" -} -,{ - "testCaseDescription": "javascript-assignment-replacement-test", - "expectedResult": { - "changes": { - "assignment.js": [ - { - "span": { - "these": [ - { - "start": [ - 1, - 5 - ], - "name": "assignment.js", - "end": [ - 1, - 6 - ] - }, - { - "start": [ - 1, - 5 - ], - "name": "assignment.js", - "end": [ - 1, - 6 - ] - } - ] - }, - "summary": "Replaced '0' with '1' in an assignment to x", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "assignment.js" - ], - "sha1": "01f04fbd4037191df6536ca1d542eb8f2678082d", - "gitDir": "test/corpus/repos/javascript", - "sha2": "95e89035c2067fbcd267d77dfdd886961f91abeb" -} -,{ - "testCaseDescription": "javascript-assignment-delete-replacement-test", - "expectedResult": { - "changes": { - "assignment.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "assignment.js", - "end": [ - 1, - 6 - ] - } - }, - "summary": "Deleted the 'x' assignment", - "tag": "JSONSummary" - }, - { - "span": { - "this": { - "start": [ - 2, - 1 - ], - "name": "assignment.js", - "end": [ - 2, - 6 - ] - } - }, - "summary": "Deleted the 'x' assignment", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "assignment.js", - "end": [ - 2, - 6 - ] - } - }, - "summary": "Added the 'x' assignment", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "assignment.js" - ], - "sha1": "95e89035c2067fbcd267d77dfdd886961f91abeb", - "gitDir": "test/corpus/repos/javascript", - "sha2": "8faa9a17a52e98b1ad0f1162f486efdfda8f8e5c" -} -,{ - "testCaseDescription": "javascript-assignment-delete-test", - "expectedResult": { - "changes": { - "assignment.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "assignment.js", - "end": [ - 1, - 6 - ] - } - }, - "summary": "Deleted the 'x' assignment", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "assignment.js" - ], - "sha1": "8faa9a17a52e98b1ad0f1162f486efdfda8f8e5c", - "gitDir": "test/corpus/repos/javascript", - "sha2": "9032da30a2fccadbd1e19d8d0d0636948a92e1e3" -} -,{ - "testCaseDescription": "javascript-assignment-delete-rest-test", - "expectedResult": { - "changes": { - "assignment.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "assignment.js", - "end": [ - 1, - 6 - ] - } - }, - "summary": "Deleted the 'x' assignment", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "assignment.js" - ], - "sha1": "9032da30a2fccadbd1e19d8d0d0636948a92e1e3", - "gitDir": "test/corpus/repos/javascript", - "sha2": "24ea895fcb8c904a8d057c536eb56be4a8928e33" -}] diff --git a/test/corpus/diff-summaries/javascript/bitwise-operator.json b/test/corpus/diff-summaries/javascript/bitwise-operator.json deleted file mode 100644 index fed05f18a..000000000 --- a/test/corpus/diff-summaries/javascript/bitwise-operator.json +++ /dev/null @@ -1,308 +0,0 @@ -[{ - "testCaseDescription": "javascript-bitwise-operator-insert-test", - "expectedResult": { - "changes": { - "bitwise-operator.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "bitwise-operator.js", - "end": [ - 1, - 7 - ] - } - }, - "summary": "Added the 'i >> j' bitwise operator", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "bitwise-operator.js" - ], - "sha1": "e50fb0bfd581bcee25d02606b04bc985c4e8c2d5", - "gitDir": "test/corpus/repos/javascript", - "sha2": "ea02f16ab7419b380ec808099788e04be860b436" -} -,{ - "testCaseDescription": "javascript-bitwise-operator-replacement-insert-test", - "expectedResult": { - "changes": { - "bitwise-operator.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "bitwise-operator.js", - "end": [ - 1, - 7 - ] - } - }, - "summary": "Added the 'i >> k' bitwise operator", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "bitwise-operator.js", - "end": [ - 2, - 7 - ] - } - }, - "summary": "Added the 'i >> j' bitwise operator", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "bitwise-operator.js" - ], - "sha1": "ea02f16ab7419b380ec808099788e04be860b436", - "gitDir": "test/corpus/repos/javascript", - "sha2": "f9001c917ef267da3f658296ca2acf5593d3782e" -} -,{ - "testCaseDescription": "javascript-bitwise-operator-delete-insert-test", - "expectedResult": { - "changes": { - "bitwise-operator.js": [ - { - "span": { - "these": [ - { - "start": [ - 1, - 6 - ], - "name": "bitwise-operator.js", - "end": [ - 1, - 7 - ] - }, - { - "start": [ - 1, - 6 - ], - "name": "bitwise-operator.js", - "end": [ - 1, - 7 - ] - } - ] - }, - "summary": "Replaced the 'k' identifier with the 'j' identifier", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "bitwise-operator.js" - ], - "sha1": "f9001c917ef267da3f658296ca2acf5593d3782e", - "gitDir": "test/corpus/repos/javascript", - "sha2": "580bdafd78d48683a535d1da85a0f9810e776bca" -} -,{ - "testCaseDescription": "javascript-bitwise-operator-replacement-test", - "expectedResult": { - "changes": { - "bitwise-operator.js": [ - { - "span": { - "these": [ - { - "start": [ - 1, - 6 - ], - "name": "bitwise-operator.js", - "end": [ - 1, - 7 - ] - }, - { - "start": [ - 1, - 6 - ], - "name": "bitwise-operator.js", - "end": [ - 1, - 7 - ] - } - ] - }, - "summary": "Replaced the 'j' identifier with the 'k' identifier", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "bitwise-operator.js" - ], - "sha1": "580bdafd78d48683a535d1da85a0f9810e776bca", - "gitDir": "test/corpus/repos/javascript", - "sha2": "3ca9b47b8791704f4d65314daf724c3ff3b77ad3" -} -,{ - "testCaseDescription": "javascript-bitwise-operator-delete-replacement-test", - "expectedResult": { - "changes": { - "bitwise-operator.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "bitwise-operator.js", - "end": [ - 1, - 7 - ] - } - }, - "summary": "Deleted the 'i >> k' bitwise operator", - "tag": "JSONSummary" - }, - { - "span": { - "this": { - "start": [ - 2, - 1 - ], - "name": "bitwise-operator.js", - "end": [ - 2, - 7 - ] - } - }, - "summary": "Deleted the 'i >> j' bitwise operator", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "bitwise-operator.js", - "end": [ - 2, - 7 - ] - } - }, - "summary": "Added the 'i >> k' bitwise operator", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "bitwise-operator.js" - ], - "sha1": "3ca9b47b8791704f4d65314daf724c3ff3b77ad3", - "gitDir": "test/corpus/repos/javascript", - "sha2": "74883181e363b757e7e66fa0e4fc525854b0ce1c" -} -,{ - "testCaseDescription": "javascript-bitwise-operator-delete-test", - "expectedResult": { - "changes": { - "bitwise-operator.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "bitwise-operator.js", - "end": [ - 1, - 7 - ] - } - }, - "summary": "Deleted the 'i >> j' bitwise operator", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "bitwise-operator.js" - ], - "sha1": "74883181e363b757e7e66fa0e4fc525854b0ce1c", - "gitDir": "test/corpus/repos/javascript", - "sha2": "3f724f4ce7be26db4a43de14aaefcec5c253c2f0" -} -,{ - "testCaseDescription": "javascript-bitwise-operator-delete-rest-test", - "expectedResult": { - "changes": { - "bitwise-operator.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "bitwise-operator.js", - "end": [ - 1, - 7 - ] - } - }, - "summary": "Deleted the 'i >> k' bitwise operator", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "bitwise-operator.js" - ], - "sha1": "3f724f4ce7be26db4a43de14aaefcec5c253c2f0", - "gitDir": "test/corpus/repos/javascript", - "sha2": "8cdb0cc77bfe88b76c86dcde66d08f97f11182f3" -}] diff --git a/test/corpus/diff-summaries/javascript/boolean-operator.json b/test/corpus/diff-summaries/javascript/boolean-operator.json deleted file mode 100644 index 340eddd16..000000000 --- a/test/corpus/diff-summaries/javascript/boolean-operator.json +++ /dev/null @@ -1,208 +0,0 @@ -[{ - "testCaseDescription": "javascript-boolean-operator-insert-test", - "expectedResult": { - "changes": { - "boolean-operator.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "boolean-operator.js", - "end": [ - 1, - 7 - ] - } - }, - "summary": "Added the 'i || j' boolean operator", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "boolean-operator.js" - ], - "sha1": "d7edfafd0028d88e036ad5af083bd4c0eaf821d5", - "gitDir": "test/corpus/repos/javascript", - "sha2": "c1fd7ccb58cd391d8a2cb427baf9451e6ef0734c" -} -,{ - "testCaseDescription": "javascript-boolean-operator-replacement-insert-test", - "expectedResult": { - "changes": { - "boolean-operator.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "boolean-operator.js", - "end": [ - 1, - 7 - ] - } - }, - "summary": "Added the 'i && j' boolean operator", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "boolean-operator.js", - "end": [ - 2, - 7 - ] - } - }, - "summary": "Added the 'i || j' boolean operator", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "boolean-operator.js" - ], - "sha1": "c1fd7ccb58cd391d8a2cb427baf9451e6ef0734c", - "gitDir": "test/corpus/repos/javascript", - "sha2": "029b382cce42f0b823e8f6c7fa383b3236d7f831" -} -,{ - "testCaseDescription": "javascript-boolean-operator-delete-insert-test", - "expectedResult": { - "changes": {}, - "errors": {} - }, - "filePaths": [ - "boolean-operator.js" - ], - "sha1": "029b382cce42f0b823e8f6c7fa383b3236d7f831", - "gitDir": "test/corpus/repos/javascript", - "sha2": "8fef1ef2ddf9da13147ee48a19dd104f020b4f1d" -} -,{ - "testCaseDescription": "javascript-boolean-operator-replacement-test", - "expectedResult": { - "changes": {}, - "errors": {} - }, - "filePaths": [ - "boolean-operator.js" - ], - "sha1": "8fef1ef2ddf9da13147ee48a19dd104f020b4f1d", - "gitDir": "test/corpus/repos/javascript", - "sha2": "4f3d6544f9d7e379865cc08309dc7276695d864c" -} -,{ - "testCaseDescription": "javascript-boolean-operator-delete-replacement-test", - "expectedResult": { - "changes": { - "boolean-operator.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "boolean-operator.js", - "end": [ - 1, - 7 - ] - } - }, - "summary": "Deleted the 'i && j' boolean operator", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "boolean-operator.js" - ], - "sha1": "4f3d6544f9d7e379865cc08309dc7276695d864c", - "gitDir": "test/corpus/repos/javascript", - "sha2": "15041bb73bf8501e01192e57cfdd6f1d889776e9" -} -,{ - "testCaseDescription": "javascript-boolean-operator-delete-test", - "expectedResult": { - "changes": { - "boolean-operator.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "boolean-operator.js", - "end": [ - 1, - 7 - ] - } - }, - "summary": "Deleted the 'i || j' boolean operator", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "boolean-operator.js" - ], - "sha1": "15041bb73bf8501e01192e57cfdd6f1d889776e9", - "gitDir": "test/corpus/repos/javascript", - "sha2": "d5a15780faa29b2762f02eba66a6d4c4e3510b8f" -} -,{ - "testCaseDescription": "javascript-boolean-operator-delete-rest-test", - "expectedResult": { - "changes": { - "boolean-operator.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "boolean-operator.js", - "end": [ - 1, - 7 - ] - } - }, - "summary": "Deleted the 'i && j' boolean operator", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "boolean-operator.js" - ], - "sha1": "d5a15780faa29b2762f02eba66a6d4c4e3510b8f", - "gitDir": "test/corpus/repos/javascript", - "sha2": "e50fb0bfd581bcee25d02606b04bc985c4e8c2d5" -}] diff --git a/test/corpus/diff-summaries/javascript/chained-callbacks.json b/test/corpus/diff-summaries/javascript/chained-callbacks.json deleted file mode 100644 index 963756c61..000000000 --- a/test/corpus/diff-summaries/javascript/chained-callbacks.json +++ /dev/null @@ -1,428 +0,0 @@ -[{ - "testCaseDescription": "javascript-chained-callbacks-insert-test", - "expectedResult": { - "changes": { - "chained-callbacks.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "chained-callbacks.js", - "end": [ - 1, - 39 - ] - } - }, - "summary": "Added the 'this.map(…)' method call", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "chained-callbacks.js" - ], - "sha1": "3717d88f796c52203c37c0d8440b823c78192c49", - "gitDir": "test/corpus/repos/javascript", - "sha2": "72ab8f58d72d44c1059e734e3a396d97eb072f23" -} -,{ - "testCaseDescription": "javascript-chained-callbacks-replacement-insert-test", - "expectedResult": { - "changes": { - "chained-callbacks.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "chained-callbacks.js", - "end": [ - 1, - 42 - ] - } - }, - "summary": "Added the 'this.reduce(…)' method call", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "chained-callbacks.js", - "end": [ - 2, - 39 - ] - } - }, - "summary": "Added the 'this.map(…)' method call", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "chained-callbacks.js" - ], - "sha1": "72ab8f58d72d44c1059e734e3a396d97eb072f23", - "gitDir": "test/corpus/repos/javascript", - "sha2": "57f2199dba16641866f45c7554c0bbb5b912dc36" -} -,{ - "testCaseDescription": "javascript-chained-callbacks-delete-insert-test", - "expectedResult": { - "changes": { - "chained-callbacks.js": [ - { - "span": { - "these": [ - { - "start": [ - 1, - 6 - ], - "name": "chained-callbacks.js", - "end": [ - 1, - 12 - ] - }, - { - "start": [ - 1, - 6 - ], - "name": "chained-callbacks.js", - "end": [ - 1, - 9 - ] - } - ] - }, - "summary": "Replaced the 'reduce' identifier with the 'map' identifier in the this.map(…) method call", - "tag": "JSONSummary" - }, - { - "span": { - "these": [ - { - "start": [ - 1, - 35 - ], - "name": "chained-callbacks.js", - "end": [ - 1, - 36 - ] - }, - { - "start": [ - 1, - 32 - ], - "name": "chained-callbacks.js", - "end": [ - 1, - 33 - ] - } - ] - }, - "summary": "Replaced the 'b' identifier with the 'a' identifier in the this.map(…) method call", - "tag": "JSONSummary" - }, - { - "span": { - "these": [ - { - "start": [ - 1, - 37 - ], - "name": "chained-callbacks.js", - "end": [ - 1, - 38 - ] - }, - { - "start": [ - 1, - 34 - ], - "name": "chained-callbacks.js", - "end": [ - 1, - 35 - ] - } - ] - }, - "summary": "Replaced the 'a' identifier with the 'b' identifier in the this.map(…) method call", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "chained-callbacks.js" - ], - "sha1": "57f2199dba16641866f45c7554c0bbb5b912dc36", - "gitDir": "test/corpus/repos/javascript", - "sha2": "d00c5e7da7eb6dfcdc63fa490b3e1f5c1481d41d" -} -,{ - "testCaseDescription": "javascript-chained-callbacks-replacement-test", - "expectedResult": { - "changes": { - "chained-callbacks.js": [ - { - "span": { - "these": [ - { - "start": [ - 1, - 6 - ], - "name": "chained-callbacks.js", - "end": [ - 1, - 9 - ] - }, - { - "start": [ - 1, - 6 - ], - "name": "chained-callbacks.js", - "end": [ - 1, - 12 - ] - } - ] - }, - "summary": "Replaced the 'map' identifier with the 'reduce' identifier in the this.reduce(…) method call", - "tag": "JSONSummary" - }, - { - "span": { - "these": [ - { - "start": [ - 1, - 32 - ], - "name": "chained-callbacks.js", - "end": [ - 1, - 33 - ] - }, - { - "start": [ - 1, - 35 - ], - "name": "chained-callbacks.js", - "end": [ - 1, - 36 - ] - } - ] - }, - "summary": "Replaced the 'a' identifier with the 'b' identifier in the this.reduce(…) method call", - "tag": "JSONSummary" - }, - { - "span": { - "these": [ - { - "start": [ - 1, - 34 - ], - "name": "chained-callbacks.js", - "end": [ - 1, - 35 - ] - }, - { - "start": [ - 1, - 37 - ], - "name": "chained-callbacks.js", - "end": [ - 1, - 38 - ] - } - ] - }, - "summary": "Replaced the 'b' identifier with the 'a' identifier in the this.reduce(…) method call", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "chained-callbacks.js" - ], - "sha1": "d00c5e7da7eb6dfcdc63fa490b3e1f5c1481d41d", - "gitDir": "test/corpus/repos/javascript", - "sha2": "9c042fe39e2f19c0e5f6cd64026de2a03c4c0896" -} -,{ - "testCaseDescription": "javascript-chained-callbacks-delete-replacement-test", - "expectedResult": { - "changes": { - "chained-callbacks.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "chained-callbacks.js", - "end": [ - 1, - 42 - ] - } - }, - "summary": "Deleted the 'this.reduce(…)' method call", - "tag": "JSONSummary" - }, - { - "span": { - "this": { - "start": [ - 2, - 1 - ], - "name": "chained-callbacks.js", - "end": [ - 2, - 39 - ] - } - }, - "summary": "Deleted the 'this.map(…)' method call", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "chained-callbacks.js", - "end": [ - 2, - 42 - ] - } - }, - "summary": "Added the 'this.reduce(…)' method call", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "chained-callbacks.js" - ], - "sha1": "9c042fe39e2f19c0e5f6cd64026de2a03c4c0896", - "gitDir": "test/corpus/repos/javascript", - "sha2": "6a9959f752a3845f39f9044f342173af99c4ee6f" -} -,{ - "testCaseDescription": "javascript-chained-callbacks-delete-test", - "expectedResult": { - "changes": { - "chained-callbacks.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "chained-callbacks.js", - "end": [ - 1, - 39 - ] - } - }, - "summary": "Deleted the 'this.map(…)' method call", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "chained-callbacks.js" - ], - "sha1": "6a9959f752a3845f39f9044f342173af99c4ee6f", - "gitDir": "test/corpus/repos/javascript", - "sha2": "a9b91380938e6d3842fd308280c0a638bb537ba5" -} -,{ - "testCaseDescription": "javascript-chained-callbacks-delete-rest-test", - "expectedResult": { - "changes": { - "chained-callbacks.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "chained-callbacks.js", - "end": [ - 1, - 42 - ] - } - }, - "summary": "Deleted the 'this.reduce(…)' method call", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "chained-callbacks.js" - ], - "sha1": "a9b91380938e6d3842fd308280c0a638bb537ba5", - "gitDir": "test/corpus/repos/javascript", - "sha2": "cf31ddf834d011d1d55eee3da85c70f15eea67f1" -}] diff --git a/test/corpus/diff-summaries/javascript/chained-property-access.json b/test/corpus/diff-summaries/javascript/chained-property-access.json deleted file mode 100644 index 9622ff7c4..000000000 --- a/test/corpus/diff-summaries/javascript/chained-property-access.json +++ /dev/null @@ -1,368 +0,0 @@ -[{ - "testCaseDescription": "javascript-chained-property-access-insert-test", - "expectedResult": { - "changes": { - "chained-property-access.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "chained-property-access.js", - "end": [ - 2, - 1 - ] - } - }, - "summary": "Added the 'returned.promise().done(…).fail(…)' return statement", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "chained-property-access.js" - ], - "sha1": "07c5dd47cd837cd06d7d034c049ea6002a5e0980", - "gitDir": "test/corpus/repos/javascript", - "sha2": "1c568a6a258b36c95bb3701e878ae08a1c9e79ba" -} -,{ - "testCaseDescription": "javascript-chained-property-access-replacement-insert-test", - "expectedResult": { - "changes": { - "chained-property-access.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "chained-property-access.js", - "end": [ - 2, - 1 - ] - } - }, - "summary": "Added the 'returned.promise().done(…).fail(…)' return statement", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "chained-property-access.js", - "end": [ - 3, - 1 - ] - } - }, - "summary": "Added the 'returned.promise().done(…).fail(…)' return statement", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "chained-property-access.js" - ], - "sha1": "1c568a6a258b36c95bb3701e878ae08a1c9e79ba", - "gitDir": "test/corpus/repos/javascript", - "sha2": "7abc5ff0a2ca47dde4b277648bc657d825c910d3" -} -,{ - "testCaseDescription": "javascript-chained-property-access-delete-insert-test", - "expectedResult": { - "changes": { - "chained-property-access.js": [ - { - "span": { - "these": [ - { - "start": [ - 1, - 33 - ], - "name": "chained-property-access.js", - "end": [ - 1, - 43 - ] - }, - { - "start": [ - 1, - 33 - ], - "name": "chained-property-access.js", - "end": [ - 1, - 41 - ] - } - ] - }, - "summary": "Replaced the 'otherDefer' identifier with the 'newDefer' identifier in the returned.promise().done(…) method call", - "tag": "JSONSummary" - }, - { - "span": { - "these": [ - { - "start": [ - 1, - 60 - ], - "name": "chained-property-access.js", - "end": [ - 1, - 70 - ] - }, - { - "start": [ - 1, - 58 - ], - "name": "chained-property-access.js", - "end": [ - 1, - 66 - ] - } - ] - }, - "summary": "Replaced the 'otherDefer' identifier with the 'newDefer' identifier in the returned.promise().done(…).fail(…) method call", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "chained-property-access.js" - ], - "sha1": "7abc5ff0a2ca47dde4b277648bc657d825c910d3", - "gitDir": "test/corpus/repos/javascript", - "sha2": "6b0bfd2f77ff616e1f944328fbcac86513799b91" -} -,{ - "testCaseDescription": "javascript-chained-property-access-replacement-test", - "expectedResult": { - "changes": { - "chained-property-access.js": [ - { - "span": { - "these": [ - { - "start": [ - 1, - 33 - ], - "name": "chained-property-access.js", - "end": [ - 1, - 41 - ] - }, - { - "start": [ - 1, - 33 - ], - "name": "chained-property-access.js", - "end": [ - 1, - 43 - ] - } - ] - }, - "summary": "Replaced the 'newDefer' identifier with the 'otherDefer' identifier in the returned.promise().done(…) method call", - "tag": "JSONSummary" - }, - { - "span": { - "these": [ - { - "start": [ - 1, - 58 - ], - "name": "chained-property-access.js", - "end": [ - 1, - 66 - ] - }, - { - "start": [ - 1, - 60 - ], - "name": "chained-property-access.js", - "end": [ - 1, - 70 - ] - } - ] - }, - "summary": "Replaced the 'newDefer' identifier with the 'otherDefer' identifier in the returned.promise().done(…).fail(…) method call", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "chained-property-access.js" - ], - "sha1": "6b0bfd2f77ff616e1f944328fbcac86513799b91", - "gitDir": "test/corpus/repos/javascript", - "sha2": "f87e928b3a52d1d9457b8389cc414276799c70c6" -} -,{ - "testCaseDescription": "javascript-chained-property-access-delete-replacement-test", - "expectedResult": { - "changes": { - "chained-property-access.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "chained-property-access.js", - "end": [ - 2, - 1 - ] - } - }, - "summary": "Deleted the 'returned.promise().done(…).fail(…)' return statement", - "tag": "JSONSummary" - }, - { - "span": { - "this": { - "start": [ - 2, - 1 - ], - "name": "chained-property-access.js", - "end": [ - 3, - 1 - ] - } - }, - "summary": "Deleted the 'returned.promise().done(…).fail(…)' return statement", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "chained-property-access.js", - "end": [ - 3, - 1 - ] - } - }, - "summary": "Added the 'returned.promise().done(…).fail(…)' return statement", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "chained-property-access.js" - ], - "sha1": "f87e928b3a52d1d9457b8389cc414276799c70c6", - "gitDir": "test/corpus/repos/javascript", - "sha2": "1056591b7f8f24ed7718a8d9b3f515eb0b48a29a" -} -,{ - "testCaseDescription": "javascript-chained-property-access-delete-test", - "expectedResult": { - "changes": { - "chained-property-access.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "chained-property-access.js", - "end": [ - 2, - 1 - ] - } - }, - "summary": "Deleted the 'returned.promise().done(…).fail(…)' return statement", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "chained-property-access.js" - ], - "sha1": "1056591b7f8f24ed7718a8d9b3f515eb0b48a29a", - "gitDir": "test/corpus/repos/javascript", - "sha2": "de450f4e2eb24b89b5d66301b772d4f9714e7919" -} -,{ - "testCaseDescription": "javascript-chained-property-access-delete-rest-test", - "expectedResult": { - "changes": { - "chained-property-access.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "chained-property-access.js", - "end": [ - 2, - 1 - ] - } - }, - "summary": "Deleted the 'returned.promise().done(…).fail(…)' return statement", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "chained-property-access.js" - ], - "sha1": "de450f4e2eb24b89b5d66301b772d4f9714e7919", - "gitDir": "test/corpus/repos/javascript", - "sha2": "3717d88f796c52203c37c0d8440b823c78192c49" -}] diff --git a/test/corpus/diff-summaries/javascript/class.json b/test/corpus/diff-summaries/javascript/class.json deleted file mode 100644 index f15fe99a2..000000000 --- a/test/corpus/diff-summaries/javascript/class.json +++ /dev/null @@ -1,428 +0,0 @@ -[{ - "testCaseDescription": "javascript-class-insert-test", - "expectedResult": { - "changes": { - "class.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "class.js", - "end": [ - 1, - 87 - ] - } - }, - "summary": "Added the 'Foo' class", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "class.js" - ], - "sha1": "05ac6c8e85dcf3c89620fde92c3f7cccf4ca5d18", - "gitDir": "test/corpus/repos/javascript", - "sha2": "d0516334378ca54458689813316ca9f3e792b9d0" -} -,{ - "testCaseDescription": "javascript-class-replacement-insert-test", - "expectedResult": { - "changes": { - "class.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "class.js", - "end": [ - 1, - 85 - ] - } - }, - "summary": "Added the 'Foo' class", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "class.js", - "end": [ - 2, - 87 - ] - } - }, - "summary": "Added the 'Foo' class", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "class.js" - ], - "sha1": "d0516334378ca54458689813316ca9f3e792b9d0", - "gitDir": "test/corpus/repos/javascript", - "sha2": "f0d1b629278eb502b25fd9d266065451cdd48405" -} -,{ - "testCaseDescription": "javascript-class-delete-insert-test", - "expectedResult": { - "changes": { - "class.js": [ - { - "span": { - "these": [ - { - "start": [ - 1, - 20 - ], - "name": "class.js", - "end": [ - 1, - 23 - ] - }, - { - "start": [ - 1, - 20 - ], - "name": "class.js", - "end": [ - 1, - 23 - ] - } - ] - }, - "summary": "Replaced the 'foo' identifier with the 'one' identifier in the one method of the 'Foo' class", - "tag": "JSONSummary" - }, - { - "span": { - "these": [ - { - "start": [ - 1, - 42 - ], - "name": "class.js", - "end": [ - 1, - 45 - ] - }, - { - "start": [ - 1, - 42 - ], - "name": "class.js", - "end": [ - 1, - 45 - ] - } - ] - }, - "summary": "Replaced the 'bar' identifier with the 'two' identifier in the two method of the 'Foo' class", - "tag": "JSONSummary" - }, - { - "span": { - "these": [ - { - "start": [ - 1, - 63 - ], - "name": "class.js", - "end": [ - 1, - 66 - ] - }, - { - "start": [ - 1, - 63 - ], - "name": "class.js", - "end": [ - 1, - 68 - ] - } - ] - }, - "summary": "Replaced the 'baz' identifier with the 'three' identifier in the three method of the 'Foo' class", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "class.js" - ], - "sha1": "f0d1b629278eb502b25fd9d266065451cdd48405", - "gitDir": "test/corpus/repos/javascript", - "sha2": "287224754bbb2fc1d5d3e66af924ab2e4b1a6e15" -} -,{ - "testCaseDescription": "javascript-class-replacement-test", - "expectedResult": { - "changes": { - "class.js": [ - { - "span": { - "these": [ - { - "start": [ - 1, - 20 - ], - "name": "class.js", - "end": [ - 1, - 23 - ] - }, - { - "start": [ - 1, - 20 - ], - "name": "class.js", - "end": [ - 1, - 23 - ] - } - ] - }, - "summary": "Replaced the 'one' identifier with the 'foo' identifier in the foo method of the 'Foo' class", - "tag": "JSONSummary" - }, - { - "span": { - "these": [ - { - "start": [ - 1, - 42 - ], - "name": "class.js", - "end": [ - 1, - 45 - ] - }, - { - "start": [ - 1, - 42 - ], - "name": "class.js", - "end": [ - 1, - 45 - ] - } - ] - }, - "summary": "Replaced the 'two' identifier with the 'bar' identifier in the bar method of the 'Foo' class", - "tag": "JSONSummary" - }, - { - "span": { - "these": [ - { - "start": [ - 1, - 63 - ], - "name": "class.js", - "end": [ - 1, - 68 - ] - }, - { - "start": [ - 1, - 63 - ], - "name": "class.js", - "end": [ - 1, - 66 - ] - } - ] - }, - "summary": "Replaced the 'three' identifier with the 'baz' identifier in the baz method of the 'Foo' class", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "class.js" - ], - "sha1": "287224754bbb2fc1d5d3e66af924ab2e4b1a6e15", - "gitDir": "test/corpus/repos/javascript", - "sha2": "faf44add1dac5da1190877cfbe29f2166a87cb70" -} -,{ - "testCaseDescription": "javascript-class-delete-replacement-test", - "expectedResult": { - "changes": { - "class.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "class.js", - "end": [ - 1, - 85 - ] - } - }, - "summary": "Deleted the 'Foo' class", - "tag": "JSONSummary" - }, - { - "span": { - "this": { - "start": [ - 2, - 1 - ], - "name": "class.js", - "end": [ - 2, - 87 - ] - } - }, - "summary": "Deleted the 'Foo' class", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "class.js", - "end": [ - 2, - 85 - ] - } - }, - "summary": "Added the 'Foo' class", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "class.js" - ], - "sha1": "faf44add1dac5da1190877cfbe29f2166a87cb70", - "gitDir": "test/corpus/repos/javascript", - "sha2": "c9d86ff39cf88d63bef375c0f1f6bee48fad7469" -} -,{ - "testCaseDescription": "javascript-class-delete-test", - "expectedResult": { - "changes": { - "class.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "class.js", - "end": [ - 1, - 87 - ] - } - }, - "summary": "Deleted the 'Foo' class", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "class.js" - ], - "sha1": "c9d86ff39cf88d63bef375c0f1f6bee48fad7469", - "gitDir": "test/corpus/repos/javascript", - "sha2": "925c03b275a76023914adc08c757bb7375f31bbd" -} -,{ - "testCaseDescription": "javascript-class-delete-rest-test", - "expectedResult": { - "changes": { - "class.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "class.js", - "end": [ - 1, - 85 - ] - } - }, - "summary": "Deleted the 'Foo' class", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "class.js" - ], - "sha1": "925c03b275a76023914adc08c757bb7375f31bbd", - "gitDir": "test/corpus/repos/javascript", - "sha2": "72a672d52b6952c146edab2927b3b05abd022921" -}] diff --git a/test/corpus/diff-summaries/javascript/comma-operator.json b/test/corpus/diff-summaries/javascript/comma-operator.json deleted file mode 100644 index b1fc0babb..000000000 --- a/test/corpus/diff-summaries/javascript/comma-operator.json +++ /dev/null @@ -1,418 +0,0 @@ -[{ - "testCaseDescription": "javascript-comma-operator-insert-test", - "expectedResult": { - "changes": { - "comma-operator.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "comma-operator.js", - "end": [ - 1, - 6 - ] - } - }, - "summary": "Added the 'a' assignment", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 1, - 8 - ], - "name": "comma-operator.js", - "end": [ - 1, - 13 - ] - } - }, - "summary": "Added the 'b' assignment", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "comma-operator.js" - ], - "sha1": "ea966e7428b15b541246b765517db3f0ef1c6af8", - "gitDir": "test/corpus/repos/javascript", - "sha2": "89fefd3a2c9fb540528c4000768a6ef747cd59d0" -} -,{ - "testCaseDescription": "javascript-comma-operator-replacement-insert-test", - "expectedResult": { - "changes": { - "comma-operator.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "comma-operator.js", - "end": [ - 1, - 23 - ] - } - }, - "summary": "Added the 'c' assignment", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "comma-operator.js", - "end": [ - 2, - 6 - ] - } - }, - "summary": "Added the 'a' assignment", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 8 - ], - "name": "comma-operator.js", - "end": [ - 2, - 13 - ] - } - }, - "summary": "Added the 'b' assignment", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "comma-operator.js" - ], - "sha1": "89fefd3a2c9fb540528c4000768a6ef747cd59d0", - "gitDir": "test/corpus/repos/javascript", - "sha2": "d18b8317fdd54ea56ecc8a6f5163100fbb90804f" -} -,{ - "testCaseDescription": "javascript-comma-operator-delete-insert-test", - "expectedResult": { - "changes": { - "comma-operator.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "comma-operator.js", - "end": [ - 1, - 6 - ] - } - }, - "summary": "Added the 'a' assignment", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 1, - 8 - ], - "name": "comma-operator.js", - "end": [ - 1, - 13 - ] - } - }, - "summary": "Added the 'b' assignment", - "tag": "JSONSummary" - }, - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "comma-operator.js", - "end": [ - 1, - 23 - ] - } - }, - "summary": "Deleted the 'c' assignment", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "comma-operator.js" - ], - "sha1": "d18b8317fdd54ea56ecc8a6f5163100fbb90804f", - "gitDir": "test/corpus/repos/javascript", - "sha2": "004af9fd96c38181e344af8dab95b192f1c1dfe2" -} -,{ - "testCaseDescription": "javascript-comma-operator-replacement-test", - "expectedResult": { - "changes": { - "comma-operator.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "comma-operator.js", - "end": [ - 1, - 23 - ] - } - }, - "summary": "Added the 'c' assignment", - "tag": "JSONSummary" - }, - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "comma-operator.js", - "end": [ - 1, - 6 - ] - } - }, - "summary": "Deleted the 'a' assignment", - "tag": "JSONSummary" - }, - { - "span": { - "this": { - "start": [ - 1, - 8 - ], - "name": "comma-operator.js", - "end": [ - 1, - 13 - ] - } - }, - "summary": "Deleted the 'b' assignment", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "comma-operator.js" - ], - "sha1": "004af9fd96c38181e344af8dab95b192f1c1dfe2", - "gitDir": "test/corpus/repos/javascript", - "sha2": "0d2764a507da37777c1f1726fba8261b84f7bcb0" -} -,{ - "testCaseDescription": "javascript-comma-operator-delete-replacement-test", - "expectedResult": { - "changes": { - "comma-operator.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "comma-operator.js", - "end": [ - 1, - 23 - ] - } - }, - "summary": "Deleted the 'c' assignment", - "tag": "JSONSummary" - }, - { - "span": { - "this": { - "start": [ - 2, - 1 - ], - "name": "comma-operator.js", - "end": [ - 2, - 6 - ] - } - }, - "summary": "Deleted the 'a' assignment", - "tag": "JSONSummary" - }, - { - "span": { - "this": { - "start": [ - 2, - 8 - ], - "name": "comma-operator.js", - "end": [ - 2, - 13 - ] - } - }, - "summary": "Deleted the 'b' assignment", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "comma-operator.js", - "end": [ - 2, - 23 - ] - } - }, - "summary": "Added the 'c' assignment", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "comma-operator.js" - ], - "sha1": "0d2764a507da37777c1f1726fba8261b84f7bcb0", - "gitDir": "test/corpus/repos/javascript", - "sha2": "7ce2f66bf4aa19bb752574fed5e2416e405dd67f" -} -,{ - "testCaseDescription": "javascript-comma-operator-delete-test", - "expectedResult": { - "changes": { - "comma-operator.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "comma-operator.js", - "end": [ - 1, - 6 - ] - } - }, - "summary": "Deleted the 'a' assignment", - "tag": "JSONSummary" - }, - { - "span": { - "this": { - "start": [ - 1, - 8 - ], - "name": "comma-operator.js", - "end": [ - 1, - 13 - ] - } - }, - "summary": "Deleted the 'b' assignment", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "comma-operator.js" - ], - "sha1": "7ce2f66bf4aa19bb752574fed5e2416e405dd67f", - "gitDir": "test/corpus/repos/javascript", - "sha2": "2e0718a5d9166e53a839ce51dccca62297668a6d" -} -,{ - "testCaseDescription": "javascript-comma-operator-delete-rest-test", - "expectedResult": { - "changes": { - "comma-operator.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "comma-operator.js", - "end": [ - 1, - 23 - ] - } - }, - "summary": "Deleted the 'c' assignment", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "comma-operator.js" - ], - "sha1": "2e0718a5d9166e53a839ce51dccca62297668a6d", - "gitDir": "test/corpus/repos/javascript", - "sha2": "7d593b800284097a4d4f70fe25aebef1cbbe69c3" -}] diff --git a/test/corpus/diff-summaries/javascript/comment.json b/test/corpus/diff-summaries/javascript/comment.json deleted file mode 100644 index 86321da62..000000000 --- a/test/corpus/diff-summaries/javascript/comment.json +++ /dev/null @@ -1,308 +0,0 @@ -[{ - "testCaseDescription": "javascript-comment-insert-test", - "expectedResult": { - "changes": { - "comment.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "comment.js", - "end": [ - 1, - 22 - ] - } - }, - "summary": "Added the '// This is a property' comment", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "comment.js" - ], - "sha1": "b00fa825ca435ba80830373e95ab22dd77ce9326", - "gitDir": "test/corpus/repos/javascript", - "sha2": "2e607c097d74497502eb9b05f61574413df5a704" -} -,{ - "testCaseDescription": "javascript-comment-replacement-insert-test", - "expectedResult": { - "changes": { - "comment.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "comment.js", - "end": [ - 3, - 3 - ] - } - }, - "summary": "Added the '/*\n * This is a method\n*/' comment", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 4, - 1 - ], - "name": "comment.js", - "end": [ - 4, - 22 - ] - } - }, - "summary": "Added the '// This is a property' comment", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "comment.js" - ], - "sha1": "2e607c097d74497502eb9b05f61574413df5a704", - "gitDir": "test/corpus/repos/javascript", - "sha2": "03b1da21726c00724121764c61d9148a5561e972" -} -,{ - "testCaseDescription": "javascript-comment-delete-insert-test", - "expectedResult": { - "changes": { - "comment.js": [ - { - "span": { - "these": [ - { - "start": [ - 1, - 1 - ], - "name": "comment.js", - "end": [ - 3, - 3 - ] - }, - { - "start": [ - 1, - 1 - ], - "name": "comment.js", - "end": [ - 1, - 22 - ] - } - ] - }, - "summary": "Replaced the '/*\n * This is a method\n*/' comment with the '// This is a property' comment", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "comment.js" - ], - "sha1": "03b1da21726c00724121764c61d9148a5561e972", - "gitDir": "test/corpus/repos/javascript", - "sha2": "2bfa931c9fdb2a9e6a5362bc4edcf55fd54afc5b" -} -,{ - "testCaseDescription": "javascript-comment-replacement-test", - "expectedResult": { - "changes": { - "comment.js": [ - { - "span": { - "these": [ - { - "start": [ - 1, - 1 - ], - "name": "comment.js", - "end": [ - 1, - 22 - ] - }, - { - "start": [ - 1, - 1 - ], - "name": "comment.js", - "end": [ - 3, - 3 - ] - } - ] - }, - "summary": "Replaced the '// This is a property' comment with the '/*\n * This is a method\n*/' comment", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "comment.js" - ], - "sha1": "2bfa931c9fdb2a9e6a5362bc4edcf55fd54afc5b", - "gitDir": "test/corpus/repos/javascript", - "sha2": "16abf9f672b794a292a6328925ecb9e5b77e4e3e" -} -,{ - "testCaseDescription": "javascript-comment-delete-replacement-test", - "expectedResult": { - "changes": { - "comment.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "comment.js", - "end": [ - 3, - 3 - ] - } - }, - "summary": "Deleted the '/*\n * This is a method\n*/' comment", - "tag": "JSONSummary" - }, - { - "span": { - "this": { - "start": [ - 4, - 1 - ], - "name": "comment.js", - "end": [ - 4, - 22 - ] - } - }, - "summary": "Deleted the '// This is a property' comment", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "comment.js", - "end": [ - 4, - 3 - ] - } - }, - "summary": "Added the '/*\n * This is a method\n*/' comment", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "comment.js" - ], - "sha1": "16abf9f672b794a292a6328925ecb9e5b77e4e3e", - "gitDir": "test/corpus/repos/javascript", - "sha2": "253e6af1000fd09a2472ce58f2294e56a5b072a5" -} -,{ - "testCaseDescription": "javascript-comment-delete-test", - "expectedResult": { - "changes": { - "comment.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "comment.js", - "end": [ - 1, - 22 - ] - } - }, - "summary": "Deleted the '// This is a property' comment", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "comment.js" - ], - "sha1": "253e6af1000fd09a2472ce58f2294e56a5b072a5", - "gitDir": "test/corpus/repos/javascript", - "sha2": "5dd2f4591f46cc567e9ef4d08528a8139f329bfe" -} -,{ - "testCaseDescription": "javascript-comment-delete-rest-test", - "expectedResult": { - "changes": { - "comment.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "comment.js", - "end": [ - 3, - 3 - ] - } - }, - "summary": "Deleted the '/*\n * This is a method\n*/' comment", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "comment.js" - ], - "sha1": "5dd2f4591f46cc567e9ef4d08528a8139f329bfe", - "gitDir": "test/corpus/repos/javascript", - "sha2": "df276ed5f435d4cf1363008ae573ea99ba39e175" -}] diff --git a/test/corpus/diff-summaries/javascript/constructor-call.json b/test/corpus/diff-summaries/javascript/constructor-call.json deleted file mode 100644 index 12e5f9518..000000000 --- a/test/corpus/diff-summaries/javascript/constructor-call.json +++ /dev/null @@ -1,308 +0,0 @@ -[{ - "testCaseDescription": "javascript-constructor-call-insert-test", - "expectedResult": { - "changes": { - "constructor-call.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "constructor-call.js", - "end": [ - 1, - 27 - ] - } - }, - "summary": "Added the 'module.Klass(1, \"two\")' constructor", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "constructor-call.js" - ], - "sha1": "e5315f0371489f42d527c318faa1406833bb3c86", - "gitDir": "test/corpus/repos/javascript", - "sha2": "3ab58f25a58c73e8b63bf047879dc80453f67ca3" -} -,{ - "testCaseDescription": "javascript-constructor-call-replacement-insert-test", - "expectedResult": { - "changes": { - "constructor-call.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "constructor-call.js", - "end": [ - 1, - 29 - ] - } - }, - "summary": "Added the 'module.Klass(1, \"three\")' constructor", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "constructor-call.js", - "end": [ - 2, - 27 - ] - } - }, - "summary": "Added the 'module.Klass(1, \"two\")' constructor", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "constructor-call.js" - ], - "sha1": "3ab58f25a58c73e8b63bf047879dc80453f67ca3", - "gitDir": "test/corpus/repos/javascript", - "sha2": "1481a195f0a198d73a647c8b75da4d7dc7221894" -} -,{ - "testCaseDescription": "javascript-constructor-call-delete-insert-test", - "expectedResult": { - "changes": { - "constructor-call.js": [ - { - "span": { - "these": [ - { - "start": [ - 1, - 21 - ], - "name": "constructor-call.js", - "end": [ - 1, - 28 - ] - }, - { - "start": [ - 1, - 21 - ], - "name": "constructor-call.js", - "end": [ - 1, - 26 - ] - } - ] - }, - "summary": "Replaced the \"three\" string with the \"two\" string in the module.Klass(1, \"two\") method call", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "constructor-call.js" - ], - "sha1": "1481a195f0a198d73a647c8b75da4d7dc7221894", - "gitDir": "test/corpus/repos/javascript", - "sha2": "ba525ceaac882771bf3028d5c750f938114e96d2" -} -,{ - "testCaseDescription": "javascript-constructor-call-replacement-test", - "expectedResult": { - "changes": { - "constructor-call.js": [ - { - "span": { - "these": [ - { - "start": [ - 1, - 21 - ], - "name": "constructor-call.js", - "end": [ - 1, - 26 - ] - }, - { - "start": [ - 1, - 21 - ], - "name": "constructor-call.js", - "end": [ - 1, - 28 - ] - } - ] - }, - "summary": "Replaced the \"two\" string with the \"three\" string in the module.Klass(1, \"three\") method call", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "constructor-call.js" - ], - "sha1": "ba525ceaac882771bf3028d5c750f938114e96d2", - "gitDir": "test/corpus/repos/javascript", - "sha2": "4b4ec51a435eea48627eedf5abc5e418a1fe6a55" -} -,{ - "testCaseDescription": "javascript-constructor-call-delete-replacement-test", - "expectedResult": { - "changes": { - "constructor-call.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "constructor-call.js", - "end": [ - 1, - 29 - ] - } - }, - "summary": "Deleted the 'module.Klass(1, \"three\")' constructor", - "tag": "JSONSummary" - }, - { - "span": { - "this": { - "start": [ - 2, - 1 - ], - "name": "constructor-call.js", - "end": [ - 2, - 27 - ] - } - }, - "summary": "Deleted the 'module.Klass(1, \"two\")' constructor", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "constructor-call.js", - "end": [ - 2, - 29 - ] - } - }, - "summary": "Added the 'module.Klass(1, \"three\")' constructor", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "constructor-call.js" - ], - "sha1": "4b4ec51a435eea48627eedf5abc5e418a1fe6a55", - "gitDir": "test/corpus/repos/javascript", - "sha2": "5d2a91a3bae082f9b7805f6dfca606e93e795432" -} -,{ - "testCaseDescription": "javascript-constructor-call-delete-test", - "expectedResult": { - "changes": { - "constructor-call.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "constructor-call.js", - "end": [ - 1, - 27 - ] - } - }, - "summary": "Deleted the 'module.Klass(1, \"two\")' constructor", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "constructor-call.js" - ], - "sha1": "5d2a91a3bae082f9b7805f6dfca606e93e795432", - "gitDir": "test/corpus/repos/javascript", - "sha2": "dbb99c0fe06226687ed383f68ef1b5d4e15f35f6" -} -,{ - "testCaseDescription": "javascript-constructor-call-delete-rest-test", - "expectedResult": { - "changes": { - "constructor-call.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "constructor-call.js", - "end": [ - 1, - 29 - ] - } - }, - "summary": "Deleted the 'module.Klass(1, \"three\")' constructor", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "constructor-call.js" - ], - "sha1": "dbb99c0fe06226687ed383f68ef1b5d4e15f35f6", - "gitDir": "test/corpus/repos/javascript", - "sha2": "a871e92442fa237af75a13a311d49a15bcea9444" -}] diff --git a/test/corpus/diff-summaries/javascript/delete-operator.json b/test/corpus/diff-summaries/javascript/delete-operator.json deleted file mode 100644 index 8f619991d..000000000 --- a/test/corpus/diff-summaries/javascript/delete-operator.json +++ /dev/null @@ -1,308 +0,0 @@ -[{ - "testCaseDescription": "javascript-delete-operator-insert-test", - "expectedResult": { - "changes": { - "delete-operator.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "delete-operator.js", - "end": [ - 1, - 21 - ] - } - }, - "summary": "Added the 'delete thing['prop']' operator", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "delete-operator.js" - ], - "sha1": "0014c5d8fc3e6f9d08e268ebbb2d42919d5b4991", - "gitDir": "test/corpus/repos/javascript", - "sha2": "1bf82468139fc9bae884877d4642cb378d30e388" -} -,{ - "testCaseDescription": "javascript-delete-operator-replacement-insert-test", - "expectedResult": { - "changes": { - "delete-operator.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "delete-operator.js", - "end": [ - 1, - 18 - ] - } - }, - "summary": "Added the 'delete thing.prop' operator", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "delete-operator.js", - "end": [ - 2, - 21 - ] - } - }, - "summary": "Added the 'delete thing['prop']' operator", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "delete-operator.js" - ], - "sha1": "1bf82468139fc9bae884877d4642cb378d30e388", - "gitDir": "test/corpus/repos/javascript", - "sha2": "8daf29e348abe84e12f3876f0d414a3d1ff66133" -} -,{ - "testCaseDescription": "javascript-delete-operator-delete-insert-test", - "expectedResult": { - "changes": { - "delete-operator.js": [ - { - "span": { - "these": [ - { - "start": [ - 1, - 1 - ], - "name": "delete-operator.js", - "end": [ - 1, - 18 - ] - }, - { - "start": [ - 1, - 1 - ], - "name": "delete-operator.js", - "end": [ - 1, - 21 - ] - } - ] - }, - "summary": "Replaced the 'delete thing.prop' operator with the 'delete thing['prop']' operator", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "delete-operator.js" - ], - "sha1": "8daf29e348abe84e12f3876f0d414a3d1ff66133", - "gitDir": "test/corpus/repos/javascript", - "sha2": "c0a5da4ddc67f830084586b2327558655a70855a" -} -,{ - "testCaseDescription": "javascript-delete-operator-replacement-test", - "expectedResult": { - "changes": { - "delete-operator.js": [ - { - "span": { - "these": [ - { - "start": [ - 1, - 1 - ], - "name": "delete-operator.js", - "end": [ - 1, - 21 - ] - }, - { - "start": [ - 1, - 1 - ], - "name": "delete-operator.js", - "end": [ - 1, - 18 - ] - } - ] - }, - "summary": "Replaced the 'delete thing['prop']' operator with the 'delete thing.prop' operator", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "delete-operator.js" - ], - "sha1": "c0a5da4ddc67f830084586b2327558655a70855a", - "gitDir": "test/corpus/repos/javascript", - "sha2": "cec4caaf5abbc34a89ed4f4695648f6c07a47419" -} -,{ - "testCaseDescription": "javascript-delete-operator-delete-replacement-test", - "expectedResult": { - "changes": { - "delete-operator.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "delete-operator.js", - "end": [ - 1, - 18 - ] - } - }, - "summary": "Deleted the 'delete thing.prop' operator", - "tag": "JSONSummary" - }, - { - "span": { - "this": { - "start": [ - 2, - 1 - ], - "name": "delete-operator.js", - "end": [ - 2, - 21 - ] - } - }, - "summary": "Deleted the 'delete thing['prop']' operator", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "delete-operator.js", - "end": [ - 2, - 18 - ] - } - }, - "summary": "Added the 'delete thing.prop' operator", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "delete-operator.js" - ], - "sha1": "cec4caaf5abbc34a89ed4f4695648f6c07a47419", - "gitDir": "test/corpus/repos/javascript", - "sha2": "497cf34db38a72640cc8ce570306c591bba9f02f" -} -,{ - "testCaseDescription": "javascript-delete-operator-delete-test", - "expectedResult": { - "changes": { - "delete-operator.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "delete-operator.js", - "end": [ - 1, - 21 - ] - } - }, - "summary": "Deleted the 'delete thing['prop']' operator", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "delete-operator.js" - ], - "sha1": "497cf34db38a72640cc8ce570306c591bba9f02f", - "gitDir": "test/corpus/repos/javascript", - "sha2": "045574a46a7e7f97875d188458465b12f0c742a8" -} -,{ - "testCaseDescription": "javascript-delete-operator-delete-rest-test", - "expectedResult": { - "changes": { - "delete-operator.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "delete-operator.js", - "end": [ - 1, - 18 - ] - } - }, - "summary": "Deleted the 'delete thing.prop' operator", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "delete-operator.js" - ], - "sha1": "045574a46a7e7f97875d188458465b12f0c742a8", - "gitDir": "test/corpus/repos/javascript", - "sha2": "91bb86f2c473fce6ff1ddd4c4e25a6362131920f" -}] diff --git a/test/corpus/diff-summaries/javascript/do-while-statement.json b/test/corpus/diff-summaries/javascript/do-while-statement.json deleted file mode 100644 index 4a0b7f166..000000000 --- a/test/corpus/diff-summaries/javascript/do-while-statement.json +++ /dev/null @@ -1,368 +0,0 @@ -[{ - "testCaseDescription": "javascript-do-while-statement-insert-test", - "expectedResult": { - "changes": { - "do-while-statement.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "do-while-statement.js", - "end": [ - 1, - 42 - ] - } - }, - "summary": "Added the 'true' do/while statement", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "do-while-statement.js" - ], - "sha1": "a373c4a7201be2aa145e60cf15e0adfedc85aac5", - "gitDir": "test/corpus/repos/javascript", - "sha2": "cebe84530c2734410e83fadc8f0aeb3a6b3ce715" -} -,{ - "testCaseDescription": "javascript-do-while-statement-replacement-insert-test", - "expectedResult": { - "changes": { - "do-while-statement.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "do-while-statement.js", - "end": [ - 1, - 48 - ] - } - }, - "summary": "Added the 'false' do/while statement", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "do-while-statement.js", - "end": [ - 2, - 42 - ] - } - }, - "summary": "Added the 'true' do/while statement", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "do-while-statement.js" - ], - "sha1": "cebe84530c2734410e83fadc8f0aeb3a6b3ce715", - "gitDir": "test/corpus/repos/javascript", - "sha2": "87bbd6f72fcd3eef6b92d656dc2fe4fb9139ba94" -} -,{ - "testCaseDescription": "javascript-do-while-statement-delete-insert-test", - "expectedResult": { - "changes": { - "do-while-statement.js": [ - { - "span": { - "these": [ - { - "start": [ - 1, - 18 - ], - "name": "do-while-statement.js", - "end": [ - 1, - 29 - ] - }, - { - "start": [ - 1, - 18 - ], - "name": "do-while-statement.js", - "end": [ - 1, - 24 - ] - } - ] - }, - "summary": "Replaced the 'replacement' identifier with the 'insert' identifier in the console.log(insert) method call", - "tag": "JSONSummary" - }, - { - "span": { - "these": [ - { - "start": [ - 1, - 41 - ], - "name": "do-while-statement.js", - "end": [ - 1, - 46 - ] - }, - { - "start": [ - 1, - 36 - ], - "name": "do-while-statement.js", - "end": [ - 1, - 40 - ] - } - ] - }, - "summary": "Replaced 'false' with 'true' in the true do/while statement", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "do-while-statement.js" - ], - "sha1": "87bbd6f72fcd3eef6b92d656dc2fe4fb9139ba94", - "gitDir": "test/corpus/repos/javascript", - "sha2": "d9f0f483d83873729799b3d7daccf467ff355a13" -} -,{ - "testCaseDescription": "javascript-do-while-statement-replacement-test", - "expectedResult": { - "changes": { - "do-while-statement.js": [ - { - "span": { - "these": [ - { - "start": [ - 1, - 18 - ], - "name": "do-while-statement.js", - "end": [ - 1, - 24 - ] - }, - { - "start": [ - 1, - 18 - ], - "name": "do-while-statement.js", - "end": [ - 1, - 29 - ] - } - ] - }, - "summary": "Replaced the 'insert' identifier with the 'replacement' identifier in the console.log(replacement) method call", - "tag": "JSONSummary" - }, - { - "span": { - "these": [ - { - "start": [ - 1, - 36 - ], - "name": "do-while-statement.js", - "end": [ - 1, - 40 - ] - }, - { - "start": [ - 1, - 41 - ], - "name": "do-while-statement.js", - "end": [ - 1, - 46 - ] - } - ] - }, - "summary": "Replaced 'true' with 'false' in the false do/while statement", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "do-while-statement.js" - ], - "sha1": "d9f0f483d83873729799b3d7daccf467ff355a13", - "gitDir": "test/corpus/repos/javascript", - "sha2": "0806416202b69971446592511927fd35e2d3df53" -} -,{ - "testCaseDescription": "javascript-do-while-statement-delete-replacement-test", - "expectedResult": { - "changes": { - "do-while-statement.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "do-while-statement.js", - "end": [ - 1, - 48 - ] - } - }, - "summary": "Deleted the 'false' do/while statement", - "tag": "JSONSummary" - }, - { - "span": { - "this": { - "start": [ - 2, - 1 - ], - "name": "do-while-statement.js", - "end": [ - 2, - 42 - ] - } - }, - "summary": "Deleted the 'true' do/while statement", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "do-while-statement.js", - "end": [ - 2, - 48 - ] - } - }, - "summary": "Added the 'false' do/while statement", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "do-while-statement.js" - ], - "sha1": "0806416202b69971446592511927fd35e2d3df53", - "gitDir": "test/corpus/repos/javascript", - "sha2": "1310973b3dc9c6f7e0f20bb7842e869b5a355e7b" -} -,{ - "testCaseDescription": "javascript-do-while-statement-delete-test", - "expectedResult": { - "changes": { - "do-while-statement.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "do-while-statement.js", - "end": [ - 1, - 42 - ] - } - }, - "summary": "Deleted the 'true' do/while statement", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "do-while-statement.js" - ], - "sha1": "1310973b3dc9c6f7e0f20bb7842e869b5a355e7b", - "gitDir": "test/corpus/repos/javascript", - "sha2": "d0e72fbaf526e2beb6f4dbdbf8b91b972315ad91" -} -,{ - "testCaseDescription": "javascript-do-while-statement-delete-rest-test", - "expectedResult": { - "changes": { - "do-while-statement.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "do-while-statement.js", - "end": [ - 1, - 48 - ] - } - }, - "summary": "Deleted the 'false' do/while statement", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "do-while-statement.js" - ], - "sha1": "d0e72fbaf526e2beb6f4dbdbf8b91b972315ad91", - "gitDir": "test/corpus/repos/javascript", - "sha2": "a6c49cc7711970d9b1fdcfeef8ea1b312bcf0ace" -}] diff --git a/test/corpus/diff-summaries/javascript/export.json b/test/corpus/diff-summaries/javascript/export.json deleted file mode 100644 index 8b1948f56..000000000 --- a/test/corpus/diff-summaries/javascript/export.json +++ /dev/null @@ -1,267 +0,0 @@ -[{ - "testCaseDescription": "javascript-export-insert-test", - "expectedResult": { - "changes": { - "export.js": [ - "Added the name1, name2, name3, nameN export statement", - "Added the variable1 as name1, variable2 as name2, nameN export statement", - "Added the name1, name2, nameN export statement", - "Added the name1 = value1, name2 = value2, name3, nameN export statement", - "Added the namedFunction export statement", - "Added the anonymous() function export statement", - "Added the name1 export statement", - "Added the name1 as default export statement", - "Added the 'foo' export statement", - "Added the name1, name2, nameN from 'foo' export statement", - "Added the import1 as name1, import2 as name2, nameN from 'bar' export statement", - "Added the 'foo' export statement" - ] - }, - "errors": {} - }, - "filePaths": [ - "export.js" - ], - "sha1": "fbc5b11fcf02fc81e576ea8ec5d4e590a6a4cf6c", - "gitDir": "test/corpus/repos/javascript", - "sha2": "2a02b3c789985c3d109009301b6b75f7151dfa26" -} -,{ - "testCaseDescription": "javascript-export-replacement-insert-test", - "expectedResult": { - "changes": { - "export.js": [ - "Added the name4, name5, name6, nameZ export statement", - "Added the variable2 as name2, variable3 as name3, nameY export statement", - "Added the name3, name4, nameT export statement", - "Added the name2 = value2, name3 = value3, name4, nameO export statement", - "Added the otherNamedFunction export statement", - "Added the newName1 export statement", - "Added the anonymous() function export statement", - "Added the name2 as statement export statement", - "Added the 'baz' export statement", - "Added the name7, name8, nameP from 'buzz' export statement", - "Added the import6 as name6, import7 as name7, nameB from 'fizz' export statement", - "Added the 'fuzz' export statement", - "Added the name1, name2, name3, nameN export statement", - "Added the variable1 as name1, variable2 as name2, nameN export statement", - "Added the name1, name2, nameN export statement", - "Added the name1 = value1, name2 = value2, name3, nameN export statement", - "Added the namedFunction export statement", - "Added the anonymous() function export statement", - "Added the name1 export statement", - "Added the name1 as default export statement", - "Added the 'foo' export statement", - "Added the name1, name2, nameN from 'foo' export statement", - "Added the import1 as name1, import2 as name2, nameN from 'bar' export statement", - "Added the 'foo' export statement" - ] - }, - "errors": {} - }, - "filePaths": [ - "export.js" - ], - "sha1": "2a02b3c789985c3d109009301b6b75f7151dfa26", - "gitDir": "test/corpus/repos/javascript", - "sha2": "a86486153befecb5a8435248342ae9ee5f9bb9fe" -} -,{ - "testCaseDescription": "javascript-export-delete-insert-test", - "expectedResult": { - "changes": { - "export.js": [ - "Replaced the 'name4' identifier with the 'name1' identifier in the name1, name2, name3, nameN export statement", - "Replaced the 'name5' identifier with the 'name2' identifier in the name1, name2, name3, nameN export statement", - "Replaced the 'name6' identifier with the 'name3' identifier in the name1, name2, name3, nameN export statement", - "Replaced the 'nameZ' identifier with the 'nameN' identifier in the name1, name2, name3, nameN export statement", - "Replaced the 'variable2' identifier with the 'variable1' identifier in the variable1 as name1, variable2 as name2, nameN export statement", - "Replaced the 'name2' identifier with the 'name1' identifier in the variable1 as name1, variable2 as name2, nameN export statement", - "Replaced the 'variable3' identifier with the 'variable2' identifier in the variable1 as name1, variable2 as name2, nameN export statement", - "Replaced the 'name3' identifier with the 'name2' identifier in the variable1 as name1, variable2 as name2, nameN export statement", - "Replaced the 'nameY' identifier with the 'nameN' identifier in the variable1 as name1, variable2 as name2, nameN export statement", - "Replaced the 'name3' identifier with the 'name1' identifier in the name1, name2, nameN export statement", - "Replaced the 'name4' identifier with the 'name2' identifier in the name1, name2, nameN export statement", - "Replaced the 'nameT' identifier with the 'nameN' identifier in the name1, name2, nameN export statement", - "Replaced the 'name2' identifier with the 'name1' identifier in the name1 var assignment", - "Replaced the 'value2' identifier with the 'value1' identifier in the name1 var assignment", - "Replaced the 'name3' identifier with the 'name2' identifier in the name2 var assignment", - "Replaced the 'value3' identifier with the 'value2' identifier in the name2 var assignment", - "Replaced the 'name4' identifier with the 'name3' identifier in the name1 = value1, name2 = value2, name3, nameN export statement", - "Replaced the 'nameO' identifier with the 'nameN' identifier in the name1 = value1, name2 = value2, name3, nameN export statement", - "Added the namedFunction export statement", - "Added the anonymous() function export statement", - "Added the name1 export statement", - "Added the name1 as default export statement", - "Replaced the otherNamedFunction export statement with the 'foo' export statement", - "Added the name1, name2, nameN from 'foo' export statement", - "Added the import1 as name1, import2 as name2, nameN from 'bar' export statement", - "Added the 'foo' export statement", - "Deleted the newName1 export statement", - "Deleted the anonymous() function export statement", - "Deleted the name2 as statement export statement", - "Deleted the 'baz' export statement", - "Deleted the name7, name8, nameP from 'buzz' export statement", - "Deleted the import6 as name6, import7 as name7, nameB from 'fizz' export statement", - "Deleted the 'fuzz' export statement" - ] - }, - "errors": {} - }, - "filePaths": [ - "export.js" - ], - "sha1": "a86486153befecb5a8435248342ae9ee5f9bb9fe", - "gitDir": "test/corpus/repos/javascript", - "sha2": "7b46f842245529860476386742508d3086628b4b" -} -,{ - "testCaseDescription": "javascript-export-replacement-test", - "expectedResult": { - "changes": { - "export.js": [ - "Replaced the 'name1' identifier with the 'name4' identifier in the name4, name5, name6, nameZ export statement", - "Replaced the 'name2' identifier with the 'name5' identifier in the name4, name5, name6, nameZ export statement", - "Replaced the 'name3' identifier with the 'name6' identifier in the name4, name5, name6, nameZ export statement", - "Replaced the 'nameN' identifier with the 'nameZ' identifier in the name4, name5, name6, nameZ export statement", - "Added the variable2 as name2, variable3 as name3, nameY export statement", - "Added the name3, name4, nameT export statement", - "Added the name2 = value2, name3 = value3, name4, nameO export statement", - "Added the otherNamedFunction export statement", - "Added the newName1 export statement", - "Added the anonymous() function export statement", - "Added the name2 as statement export statement", - "Added the 'baz' export statement", - "Added the name7, name8, nameP from 'buzz' export statement", - "Added the import6 as name6, import7 as name7, nameB from 'fizz' export statement", - "Added the 'fuzz' export statement", - "Deleted the variable1 as name1, variable2 as name2, nameN export statement", - "Deleted the name1, name2, nameN export statement", - "Deleted the name1 = value1, name2 = value2, name3, nameN export statement", - "Deleted the namedFunction export statement", - "Deleted the anonymous() function export statement", - "Deleted the name1 export statement", - "Deleted the name1 as default export statement", - "Deleted the 'foo' export statement", - "Deleted the name1, name2, nameN from 'foo' export statement", - "Deleted the import1 as name1, import2 as name2, nameN from 'bar' export statement", - "Deleted the 'foo' export statement" - ] - }, - "errors": {} - }, - "filePaths": [ - "export.js" - ], - "sha1": "7b46f842245529860476386742508d3086628b4b", - "gitDir": "test/corpus/repos/javascript", - "sha2": "1586e1f5d610cc2c194478f3aeec506172299c7b" -} -,{ - "testCaseDescription": "javascript-export-delete-replacement-test", - "expectedResult": { - "changes": { - "export.js": [ - "Deleted the name4, name5, name6, nameZ export statement", - "Deleted the variable2 as name2, variable3 as name3, nameY export statement", - "Deleted the name3, name4, nameT export statement", - "Deleted the name2 = value2, name3 = value3, name4, nameO export statement", - "Deleted the otherNamedFunction export statement", - "Deleted the newName1 export statement", - "Deleted the anonymous() function export statement", - "Deleted the name2 as statement export statement", - "Deleted the 'baz' export statement", - "Deleted the name7, name8, nameP from 'buzz' export statement", - "Deleted the import6 as name6, import7 as name7, nameB from 'fizz' export statement", - "Deleted the 'fuzz' export statement", - "Deleted the name1, name2, name3, nameN export statement", - "Deleted the variable1 as name1, variable2 as name2, nameN export statement", - "Deleted the name1, name2, nameN export statement", - "Deleted the name1 = value1, name2 = value2, name3, nameN export statement", - "Deleted the namedFunction export statement", - "Deleted the anonymous() function export statement", - "Deleted the name1 export statement", - "Deleted the name1 as default export statement", - "Deleted the 'foo' export statement", - "Deleted the name1, name2, nameN from 'foo' export statement", - "Deleted the import1 as name1, import2 as name2, nameN from 'bar' export statement", - "Deleted the 'foo' export statement", - "Added the name4, name5, name6, nameZ export statement", - "Added the variable2 as name2, variable3 as name3, nameY export statement", - "Added the name3, name4, nameT export statement", - "Added the name2 = value2, name3 = value3, name4, nameO export statement", - "Added the otherNamedFunction export statement", - "Added the newName1 export statement", - "Added the anonymous() function export statement", - "Added the name2 as statement export statement", - "Added the 'baz' export statement", - "Added the name7, name8, nameP from 'buzz' export statement", - "Added the import6 as name6, import7 as name7, nameB from 'fizz' export statement", - "Added the 'fuzz' export statement" - ] - }, - "errors": {} - }, - "filePaths": [ - "export.js" - ], - "sha1": "1586e1f5d610cc2c194478f3aeec506172299c7b", - "gitDir": "test/corpus/repos/javascript", - "sha2": "8ed6038b2ae6a12b88e6139701f2fc038ee2fe60" -} -,{ - "testCaseDescription": "javascript-export-delete-test", - "expectedResult": { - "changes": { - "export.js": [ - "Deleted the name1, name2, name3, nameN export statement", - "Deleted the variable1 as name1, variable2 as name2, nameN export statement", - "Deleted the name1, name2, nameN export statement", - "Deleted the name1 = value1, name2 = value2, name3, nameN export statement", - "Deleted the namedFunction export statement", - "Deleted the anonymous() function export statement", - "Deleted the name1 export statement", - "Deleted the name1 as default export statement", - "Deleted the 'foo' export statement", - "Deleted the name1, name2, nameN from 'foo' export statement", - "Deleted the import1 as name1, import2 as name2, nameN from 'bar' export statement", - "Deleted the 'foo' export statement" - ] - }, - "errors": {} - }, - "filePaths": [ - "export.js" - ], - "sha1": "8ed6038b2ae6a12b88e6139701f2fc038ee2fe60", - "gitDir": "test/corpus/repos/javascript", - "sha2": "5fa5440ad72fb78f66fdb8163b2cb7e669a0c9f7" -} -,{ - "testCaseDescription": "javascript-export-delete-rest-test", - "expectedResult": { - "changes": { - "export.js": [ - "Deleted the name4, name5, name6, nameZ export statement", - "Deleted the variable2 as name2, variable3 as name3, nameY export statement", - "Deleted the name3, name4, nameT export statement", - "Deleted the name2 = value2, name3 = value3, name4, nameO export statement", - "Deleted the otherNamedFunction export statement", - "Deleted the newName1 export statement", - "Deleted the anonymous() function export statement", - "Deleted the name2 as statement export statement", - "Deleted the 'baz' export statement", - "Deleted the name7, name8, nameP from 'buzz' export statement", - "Deleted the import6 as name6, import7 as name7, nameB from 'fizz' export statement", - "Deleted the 'fuzz' export statement" - ] - }, - "errors": {} - }, - "filePaths": [ - "export.js" - ], - "sha1": "5fa5440ad72fb78f66fdb8163b2cb7e669a0c9f7", - "gitDir": "test/corpus/repos/javascript", - "sha2": "870c7e629a76e123abf0a4f8095499e596838bfd" -}] diff --git a/test/corpus/diff-summaries/javascript/false.json b/test/corpus/diff-summaries/javascript/false.json deleted file mode 100644 index 5d7396805..000000000 --- a/test/corpus/diff-summaries/javascript/false.json +++ /dev/null @@ -1,316 +0,0 @@ -[{ - "testCaseDescription": "javascript-false-insert-test", - "expectedResult": { - "changes": { - "false.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "false.js", - "end": [ - 1, - 6 - ] - } - }, - "summary": "Added 'false'", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "false.js" - ], - "sha1": "d1241fa4218f33189f78a91a9513ca7e2120a2a0", - "gitDir": "test/corpus/repos/javascript", - "sha2": "5c3adaccd872d776c6b837d871a79cf1f0c520ec" -} -,{ - "testCaseDescription": "javascript-false-replacement-insert-test", - "expectedResult": { - "changes": { - "false.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "false.js", - "end": [ - 1, - 14 - ] - } - }, - "summary": "Added the 'false' return statement", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "false.js", - "end": [ - 2, - 6 - ] - } - }, - "summary": "Added 'false'", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "false.js" - ], - "sha1": "5c3adaccd872d776c6b837d871a79cf1f0c520ec", - "gitDir": "test/corpus/repos/javascript", - "sha2": "791af8f5bd8ea06a1d83fe6a78788e02d2bb468d" -} -,{ - "testCaseDescription": "javascript-false-delete-insert-test", - "expectedResult": { - "changes": { - "false.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "false.js", - "end": [ - 1, - 6 - ] - } - }, - "summary": "Added 'false'", - "tag": "JSONSummary" - }, - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "false.js", - "end": [ - 1, - 14 - ] - } - }, - "summary": "Deleted the 'false' return statement", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "false.js" - ], - "sha1": "791af8f5bd8ea06a1d83fe6a78788e02d2bb468d", - "gitDir": "test/corpus/repos/javascript", - "sha2": "19b007fa1339fa0aa105833446507b6cc54688ad" -} -,{ - "testCaseDescription": "javascript-false-replacement-test", - "expectedResult": { - "changes": { - "false.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "false.js", - "end": [ - 1, - 14 - ] - } - }, - "summary": "Added the 'false' return statement", - "tag": "JSONSummary" - }, - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "false.js", - "end": [ - 1, - 6 - ] - } - }, - "summary": "Deleted 'false'", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "false.js" - ], - "sha1": "19b007fa1339fa0aa105833446507b6cc54688ad", - "gitDir": "test/corpus/repos/javascript", - "sha2": "de949429ff3d674e788d99101942f61de3beb083" -} -,{ - "testCaseDescription": "javascript-false-delete-replacement-test", - "expectedResult": { - "changes": { - "false.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "false.js", - "end": [ - 1, - 14 - ] - } - }, - "summary": "Deleted the 'false' return statement", - "tag": "JSONSummary" - }, - { - "span": { - "this": { - "start": [ - 2, - 1 - ], - "name": "false.js", - "end": [ - 2, - 6 - ] - } - }, - "summary": "Deleted 'false'", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "false.js", - "end": [ - 2, - 14 - ] - } - }, - "summary": "Added the 'false' return statement", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "false.js" - ], - "sha1": "de949429ff3d674e788d99101942f61de3beb083", - "gitDir": "test/corpus/repos/javascript", - "sha2": "a53c2421cba5ff7a05a70181604bae01a600aaa4" -} -,{ - "testCaseDescription": "javascript-false-delete-test", - "expectedResult": { - "changes": { - "false.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "false.js", - "end": [ - 1, - 6 - ] - } - }, - "summary": "Deleted 'false'", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "false.js" - ], - "sha1": "a53c2421cba5ff7a05a70181604bae01a600aaa4", - "gitDir": "test/corpus/repos/javascript", - "sha2": "06a9f053e100d69f09fa0218b8cd1b815d55f820" -} -,{ - "testCaseDescription": "javascript-false-delete-rest-test", - "expectedResult": { - "changes": { - "false.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "false.js", - "end": [ - 1, - 14 - ] - } - }, - "summary": "Deleted the 'false' return statement", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "false.js" - ], - "sha1": "06a9f053e100d69f09fa0218b8cd1b815d55f820", - "gitDir": "test/corpus/repos/javascript", - "sha2": "05ac6c8e85dcf3c89620fde92c3f7cccf4ca5d18" -}] diff --git a/test/corpus/diff-summaries/javascript/for-in-statement.json b/test/corpus/diff-summaries/javascript/for-in-statement.json deleted file mode 100644 index 8c37caf0e..000000000 --- a/test/corpus/diff-summaries/javascript/for-in-statement.json +++ /dev/null @@ -1,428 +0,0 @@ -[{ - "testCaseDescription": "javascript-for-in-statement-insert-test", - "expectedResult": { - "changes": { - "for-in-statement.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "for-in-statement.js", - "end": [ - 1, - 35 - ] - } - }, - "summary": "Added the 'thing in things' for statement", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "for-in-statement.js" - ], - "sha1": "2017d7a8b91c62e06d4de3654b0a7a2d550e55b9", - "gitDir": "test/corpus/repos/javascript", - "sha2": "9af240cfa0f7af52df4650eddcac4bbd33dd5513" -} -,{ - "testCaseDescription": "javascript-for-in-statement-replacement-insert-test", - "expectedResult": { - "changes": { - "for-in-statement.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "for-in-statement.js", - "end": [ - 1, - 32 - ] - } - }, - "summary": "Added the 'item in items' for statement", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "for-in-statement.js", - "end": [ - 2, - 35 - ] - } - }, - "summary": "Added the 'thing in things' for statement", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "for-in-statement.js" - ], - "sha1": "9af240cfa0f7af52df4650eddcac4bbd33dd5513", - "gitDir": "test/corpus/repos/javascript", - "sha2": "58da861d6aa35b1f3a741d2e32ecef9a23b3bfb9" -} -,{ - "testCaseDescription": "javascript-for-in-statement-delete-insert-test", - "expectedResult": { - "changes": { - "for-in-statement.js": [ - { - "span": { - "these": [ - { - "start": [ - 1, - 6 - ], - "name": "for-in-statement.js", - "end": [ - 1, - 10 - ] - }, - { - "start": [ - 1, - 6 - ], - "name": "for-in-statement.js", - "end": [ - 1, - 11 - ] - } - ] - }, - "summary": "Replaced the 'item' identifier with the 'thing' identifier", - "tag": "JSONSummary" - }, - { - "span": { - "these": [ - { - "start": [ - 1, - 14 - ], - "name": "for-in-statement.js", - "end": [ - 1, - 19 - ] - }, - { - "start": [ - 1, - 15 - ], - "name": "for-in-statement.js", - "end": [ - 1, - 21 - ] - } - ] - }, - "summary": "Replaced the 'items' identifier with the 'things' identifier", - "tag": "JSONSummary" - }, - { - "span": { - "these": [ - { - "start": [ - 1, - 23 - ], - "name": "for-in-statement.js", - "end": [ - 1, - 27 - ] - }, - { - "start": [ - 1, - 25 - ], - "name": "for-in-statement.js", - "end": [ - 1, - 30 - ] - } - ] - }, - "summary": "Replaced the 'item' identifier with the 'thing' identifier in the thing() function call", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "for-in-statement.js" - ], - "sha1": "58da861d6aa35b1f3a741d2e32ecef9a23b3bfb9", - "gitDir": "test/corpus/repos/javascript", - "sha2": "37df916c1924ee482548cf1b653ca2f1adc897a4" -} -,{ - "testCaseDescription": "javascript-for-in-statement-replacement-test", - "expectedResult": { - "changes": { - "for-in-statement.js": [ - { - "span": { - "these": [ - { - "start": [ - 1, - 6 - ], - "name": "for-in-statement.js", - "end": [ - 1, - 11 - ] - }, - { - "start": [ - 1, - 6 - ], - "name": "for-in-statement.js", - "end": [ - 1, - 10 - ] - } - ] - }, - "summary": "Replaced the 'thing' identifier with the 'item' identifier", - "tag": "JSONSummary" - }, - { - "span": { - "these": [ - { - "start": [ - 1, - 15 - ], - "name": "for-in-statement.js", - "end": [ - 1, - 21 - ] - }, - { - "start": [ - 1, - 14 - ], - "name": "for-in-statement.js", - "end": [ - 1, - 19 - ] - } - ] - }, - "summary": "Replaced the 'things' identifier with the 'items' identifier", - "tag": "JSONSummary" - }, - { - "span": { - "these": [ - { - "start": [ - 1, - 25 - ], - "name": "for-in-statement.js", - "end": [ - 1, - 30 - ] - }, - { - "start": [ - 1, - 23 - ], - "name": "for-in-statement.js", - "end": [ - 1, - 27 - ] - } - ] - }, - "summary": "Replaced the 'thing' identifier with the 'item' identifier in the item() function call", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "for-in-statement.js" - ], - "sha1": "37df916c1924ee482548cf1b653ca2f1adc897a4", - "gitDir": "test/corpus/repos/javascript", - "sha2": "517e2f1868a6cf33ab920bc26a84027328f44b55" -} -,{ - "testCaseDescription": "javascript-for-in-statement-delete-replacement-test", - "expectedResult": { - "changes": { - "for-in-statement.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "for-in-statement.js", - "end": [ - 1, - 32 - ] - } - }, - "summary": "Deleted the 'item in items' for statement", - "tag": "JSONSummary" - }, - { - "span": { - "this": { - "start": [ - 2, - 1 - ], - "name": "for-in-statement.js", - "end": [ - 2, - 35 - ] - } - }, - "summary": "Deleted the 'thing in things' for statement", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "for-in-statement.js", - "end": [ - 2, - 32 - ] - } - }, - "summary": "Added the 'item in items' for statement", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "for-in-statement.js" - ], - "sha1": "517e2f1868a6cf33ab920bc26a84027328f44b55", - "gitDir": "test/corpus/repos/javascript", - "sha2": "095b4a966cb6a42a638f120901337fe3937afbfc" -} -,{ - "testCaseDescription": "javascript-for-in-statement-delete-test", - "expectedResult": { - "changes": { - "for-in-statement.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "for-in-statement.js", - "end": [ - 1, - 35 - ] - } - }, - "summary": "Deleted the 'thing in things' for statement", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "for-in-statement.js" - ], - "sha1": "095b4a966cb6a42a638f120901337fe3937afbfc", - "gitDir": "test/corpus/repos/javascript", - "sha2": "994f9b8ba0c57e8397eb9bbdb74ac8503aeeb291" -} -,{ - "testCaseDescription": "javascript-for-in-statement-delete-rest-test", - "expectedResult": { - "changes": { - "for-in-statement.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "for-in-statement.js", - "end": [ - 1, - 32 - ] - } - }, - "summary": "Deleted the 'item in items' for statement", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "for-in-statement.js" - ], - "sha1": "994f9b8ba0c57e8397eb9bbdb74ac8503aeeb291", - "gitDir": "test/corpus/repos/javascript", - "sha2": "2747446a2e77138d8a05f4ac9068b6c2fefe8c3d" -}] diff --git a/test/corpus/diff-summaries/javascript/for-loop-with-in-statement.json b/test/corpus/diff-summaries/javascript/for-loop-with-in-statement.json deleted file mode 100644 index 82d26afe0..000000000 --- a/test/corpus/diff-summaries/javascript/for-loop-with-in-statement.json +++ /dev/null @@ -1,368 +0,0 @@ -[{ - "testCaseDescription": "javascript-for-loop-with-in-statement-insert-test", - "expectedResult": { - "changes": { - "for-loop-with-in-statement.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "for-loop-with-in-statement.js", - "end": [ - 1, - 63 - ] - } - }, - "summary": "Added the 'key in something && i = 0; i < n; i++' for statement", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "for-loop-with-in-statement.js" - ], - "sha1": "faab59d023f70bb2d675e7d0671d36bc82dc9d0f", - "gitDir": "test/corpus/repos/javascript", - "sha2": "184201b3796e0d955659a52b5d2b1624a9e68ef2" -} -,{ - "testCaseDescription": "javascript-for-loop-with-in-statement-replacement-insert-test", - "expectedResult": { - "changes": { - "for-loop-with-in-statement.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "for-loop-with-in-statement.js", - "end": [ - 1, - 73 - ] - } - }, - "summary": "Added the 'otherKey in something && i = 0; i < n; i++' for statement", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "for-loop-with-in-statement.js", - "end": [ - 2, - 63 - ] - } - }, - "summary": "Added the 'key in something && i = 0; i < n; i++' for statement", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "for-loop-with-in-statement.js" - ], - "sha1": "184201b3796e0d955659a52b5d2b1624a9e68ef2", - "gitDir": "test/corpus/repos/javascript", - "sha2": "586a2c3efd9651e7be12ec5ef857b734daffea6a" -} -,{ - "testCaseDescription": "javascript-for-loop-with-in-statement-delete-insert-test", - "expectedResult": { - "changes": { - "for-loop-with-in-statement.js": [ - { - "span": { - "these": [ - { - "start": [ - 1, - 6 - ], - "name": "for-loop-with-in-statement.js", - "end": [ - 1, - 14 - ] - }, - { - "start": [ - 1, - 6 - ], - "name": "for-loop-with-in-statement.js", - "end": [ - 1, - 9 - ] - } - ] - }, - "summary": "Replaced the 'otherKey' identifier with the 'key' identifier", - "tag": "JSONSummary" - }, - { - "span": { - "these": [ - { - "start": [ - 1, - 52 - ], - "name": "for-loop-with-in-statement.js", - "end": [ - 1, - 68 - ] - }, - { - "start": [ - 1, - 47 - ], - "name": "for-loop-with-in-statement.js", - "end": [ - 1, - 58 - ] - } - ] - }, - "summary": "Replaced the 'doOtherSomething' identifier with the 'doSomething' identifier in the doSomething() function call", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "for-loop-with-in-statement.js" - ], - "sha1": "586a2c3efd9651e7be12ec5ef857b734daffea6a", - "gitDir": "test/corpus/repos/javascript", - "sha2": "fd27e1f30fd033a46ad5102fdcb5505937975f3d" -} -,{ - "testCaseDescription": "javascript-for-loop-with-in-statement-replacement-test", - "expectedResult": { - "changes": { - "for-loop-with-in-statement.js": [ - { - "span": { - "these": [ - { - "start": [ - 1, - 6 - ], - "name": "for-loop-with-in-statement.js", - "end": [ - 1, - 9 - ] - }, - { - "start": [ - 1, - 6 - ], - "name": "for-loop-with-in-statement.js", - "end": [ - 1, - 14 - ] - } - ] - }, - "summary": "Replaced the 'key' identifier with the 'otherKey' identifier", - "tag": "JSONSummary" - }, - { - "span": { - "these": [ - { - "start": [ - 1, - 47 - ], - "name": "for-loop-with-in-statement.js", - "end": [ - 1, - 58 - ] - }, - { - "start": [ - 1, - 52 - ], - "name": "for-loop-with-in-statement.js", - "end": [ - 1, - 68 - ] - } - ] - }, - "summary": "Replaced the 'doSomething' identifier with the 'doOtherSomething' identifier in the doOtherSomething() function call", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "for-loop-with-in-statement.js" - ], - "sha1": "fd27e1f30fd033a46ad5102fdcb5505937975f3d", - "gitDir": "test/corpus/repos/javascript", - "sha2": "39740a3c6176bf3db5c3574e1c6ca84608c315b1" -} -,{ - "testCaseDescription": "javascript-for-loop-with-in-statement-delete-replacement-test", - "expectedResult": { - "changes": { - "for-loop-with-in-statement.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "for-loop-with-in-statement.js", - "end": [ - 1, - 73 - ] - } - }, - "summary": "Deleted the 'otherKey in something && i = 0; i < n; i++' for statement", - "tag": "JSONSummary" - }, - { - "span": { - "this": { - "start": [ - 2, - 1 - ], - "name": "for-loop-with-in-statement.js", - "end": [ - 2, - 63 - ] - } - }, - "summary": "Deleted the 'key in something && i = 0; i < n; i++' for statement", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "for-loop-with-in-statement.js", - "end": [ - 2, - 73 - ] - } - }, - "summary": "Added the 'otherKey in something && i = 0; i < n; i++' for statement", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "for-loop-with-in-statement.js" - ], - "sha1": "39740a3c6176bf3db5c3574e1c6ca84608c315b1", - "gitDir": "test/corpus/repos/javascript", - "sha2": "f438ed3707daff81f5e48c2726e9008707dd8a5a" -} -,{ - "testCaseDescription": "javascript-for-loop-with-in-statement-delete-test", - "expectedResult": { - "changes": { - "for-loop-with-in-statement.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "for-loop-with-in-statement.js", - "end": [ - 1, - 63 - ] - } - }, - "summary": "Deleted the 'key in something && i = 0; i < n; i++' for statement", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "for-loop-with-in-statement.js" - ], - "sha1": "f438ed3707daff81f5e48c2726e9008707dd8a5a", - "gitDir": "test/corpus/repos/javascript", - "sha2": "90ed63f4489e99976afa912f90bfe0a3d89a7389" -} -,{ - "testCaseDescription": "javascript-for-loop-with-in-statement-delete-rest-test", - "expectedResult": { - "changes": { - "for-loop-with-in-statement.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "for-loop-with-in-statement.js", - "end": [ - 1, - 73 - ] - } - }, - "summary": "Deleted the 'otherKey in something && i = 0; i < n; i++' for statement", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "for-loop-with-in-statement.js" - ], - "sha1": "90ed63f4489e99976afa912f90bfe0a3d89a7389", - "gitDir": "test/corpus/repos/javascript", - "sha2": "0ba7c6b1f1b67daa1a4bea6a573c1b80be0cfbbc" -}] diff --git a/test/corpus/diff-summaries/javascript/for-of-statement.json b/test/corpus/diff-summaries/javascript/for-of-statement.json deleted file mode 100644 index 15e59c7e7..000000000 --- a/test/corpus/diff-summaries/javascript/for-of-statement.json +++ /dev/null @@ -1,428 +0,0 @@ -[{ - "testCaseDescription": "javascript-for-of-statement-insert-test", - "expectedResult": { - "changes": { - "for-of-statement.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "for-of-statement.js", - "end": [ - 1, - 43 - ] - } - }, - "summary": "Added the 'item of items' for statement", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "for-of-statement.js" - ], - "sha1": "0ba7c6b1f1b67daa1a4bea6a573c1b80be0cfbbc", - "gitDir": "test/corpus/repos/javascript", - "sha2": "3d1449a3bc07b4ff653184c77efcc7eb72dd524c" -} -,{ - "testCaseDescription": "javascript-for-of-statement-replacement-insert-test", - "expectedResult": { - "changes": { - "for-of-statement.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "for-of-statement.js", - "end": [ - 1, - 46 - ] - } - }, - "summary": "Added the 'thing of things' for statement", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "for-of-statement.js", - "end": [ - 2, - 43 - ] - } - }, - "summary": "Added the 'item of items' for statement", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "for-of-statement.js" - ], - "sha1": "3d1449a3bc07b4ff653184c77efcc7eb72dd524c", - "gitDir": "test/corpus/repos/javascript", - "sha2": "31112575f86e94f481e6eb6d74dabbfef5cf8ac6" -} -,{ - "testCaseDescription": "javascript-for-of-statement-delete-insert-test", - "expectedResult": { - "changes": { - "for-of-statement.js": [ - { - "span": { - "these": [ - { - "start": [ - 1, - 10 - ], - "name": "for-of-statement.js", - "end": [ - 1, - 15 - ] - }, - { - "start": [ - 1, - 10 - ], - "name": "for-of-statement.js", - "end": [ - 1, - 14 - ] - } - ] - }, - "summary": "Replaced the 'thing' identifier with the 'item' identifier", - "tag": "JSONSummary" - }, - { - "span": { - "these": [ - { - "start": [ - 1, - 19 - ], - "name": "for-of-statement.js", - "end": [ - 1, - 25 - ] - }, - { - "start": [ - 1, - 18 - ], - "name": "for-of-statement.js", - "end": [ - 1, - 23 - ] - } - ] - }, - "summary": "Replaced the 'things' identifier with the 'items' identifier", - "tag": "JSONSummary" - }, - { - "span": { - "these": [ - { - "start": [ - 1, - 37 - ], - "name": "for-of-statement.js", - "end": [ - 1, - 42 - ] - }, - { - "start": [ - 1, - 35 - ], - "name": "for-of-statement.js", - "end": [ - 1, - 39 - ] - } - ] - }, - "summary": "Replaced the 'thing' identifier with the 'item' identifier in the process(item) function call", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "for-of-statement.js" - ], - "sha1": "31112575f86e94f481e6eb6d74dabbfef5cf8ac6", - "gitDir": "test/corpus/repos/javascript", - "sha2": "bd5d2e141cbee15d933dcfe3eecf04cdda94f256" -} -,{ - "testCaseDescription": "javascript-for-of-statement-replacement-test", - "expectedResult": { - "changes": { - "for-of-statement.js": [ - { - "span": { - "these": [ - { - "start": [ - 1, - 10 - ], - "name": "for-of-statement.js", - "end": [ - 1, - 14 - ] - }, - { - "start": [ - 1, - 10 - ], - "name": "for-of-statement.js", - "end": [ - 1, - 15 - ] - } - ] - }, - "summary": "Replaced the 'item' identifier with the 'thing' identifier", - "tag": "JSONSummary" - }, - { - "span": { - "these": [ - { - "start": [ - 1, - 18 - ], - "name": "for-of-statement.js", - "end": [ - 1, - 23 - ] - }, - { - "start": [ - 1, - 19 - ], - "name": "for-of-statement.js", - "end": [ - 1, - 25 - ] - } - ] - }, - "summary": "Replaced the 'items' identifier with the 'things' identifier", - "tag": "JSONSummary" - }, - { - "span": { - "these": [ - { - "start": [ - 1, - 35 - ], - "name": "for-of-statement.js", - "end": [ - 1, - 39 - ] - }, - { - "start": [ - 1, - 37 - ], - "name": "for-of-statement.js", - "end": [ - 1, - 42 - ] - } - ] - }, - "summary": "Replaced the 'item' identifier with the 'thing' identifier in the process(thing) function call", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "for-of-statement.js" - ], - "sha1": "bd5d2e141cbee15d933dcfe3eecf04cdda94f256", - "gitDir": "test/corpus/repos/javascript", - "sha2": "e868cdc733c04e540ccca5a4fd9b29055ff48b89" -} -,{ - "testCaseDescription": "javascript-for-of-statement-delete-replacement-test", - "expectedResult": { - "changes": { - "for-of-statement.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "for-of-statement.js", - "end": [ - 1, - 46 - ] - } - }, - "summary": "Deleted the 'thing of things' for statement", - "tag": "JSONSummary" - }, - { - "span": { - "this": { - "start": [ - 2, - 1 - ], - "name": "for-of-statement.js", - "end": [ - 2, - 43 - ] - } - }, - "summary": "Deleted the 'item of items' for statement", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "for-of-statement.js", - "end": [ - 2, - 46 - ] - } - }, - "summary": "Added the 'thing of things' for statement", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "for-of-statement.js" - ], - "sha1": "e868cdc733c04e540ccca5a4fd9b29055ff48b89", - "gitDir": "test/corpus/repos/javascript", - "sha2": "eaa9c7d29fd865d30edc381723685ce4bdd3b3c0" -} -,{ - "testCaseDescription": "javascript-for-of-statement-delete-test", - "expectedResult": { - "changes": { - "for-of-statement.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "for-of-statement.js", - "end": [ - 1, - 43 - ] - } - }, - "summary": "Deleted the 'item of items' for statement", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "for-of-statement.js" - ], - "sha1": "eaa9c7d29fd865d30edc381723685ce4bdd3b3c0", - "gitDir": "test/corpus/repos/javascript", - "sha2": "96274519618035299d535a46b5a9b09a88c624de" -} -,{ - "testCaseDescription": "javascript-for-of-statement-delete-rest-test", - "expectedResult": { - "changes": { - "for-of-statement.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "for-of-statement.js", - "end": [ - 1, - 46 - ] - } - }, - "summary": "Deleted the 'thing of things' for statement", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "for-of-statement.js" - ], - "sha1": "96274519618035299d535a46b5a9b09a88c624de", - "gitDir": "test/corpus/repos/javascript", - "sha2": "1e95946698829d93a91686c01b91618eb065b077" -}] diff --git a/test/corpus/diff-summaries/javascript/for-statement.json b/test/corpus/diff-summaries/javascript/for-statement.json deleted file mode 100644 index 05671f8d5..000000000 --- a/test/corpus/diff-summaries/javascript/for-statement.json +++ /dev/null @@ -1,308 +0,0 @@ -[{ - "testCaseDescription": "javascript-for-statement-insert-test", - "expectedResult": { - "changes": { - "for-statement.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "for-statement.js", - "end": [ - 1, - 45 - ] - } - }, - "summary": "Added the 'i = 0, init(); i < 10; i++' for statement", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "for-statement.js" - ], - "sha1": "761990749004312c4b5e474eeacb839376523f0b", - "gitDir": "test/corpus/repos/javascript", - "sha2": "720e97a0bc939ae883e7bbe18a84f02b8abeeb7a" -} -,{ - "testCaseDescription": "javascript-for-statement-replacement-insert-test", - "expectedResult": { - "changes": { - "for-statement.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "for-statement.js", - "end": [ - 1, - 46 - ] - } - }, - "summary": "Added the 'i = 0, init(); i < 100; i++' for statement", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "for-statement.js", - "end": [ - 2, - 45 - ] - } - }, - "summary": "Added the 'i = 0, init(); i < 10; i++' for statement", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "for-statement.js" - ], - "sha1": "720e97a0bc939ae883e7bbe18a84f02b8abeeb7a", - "gitDir": "test/corpus/repos/javascript", - "sha2": "f4a0a3f223f66ace49c2e2894579639324035b85" -} -,{ - "testCaseDescription": "javascript-for-statement-delete-insert-test", - "expectedResult": { - "changes": { - "for-statement.js": [ - { - "span": { - "these": [ - { - "start": [ - 1, - 25 - ], - "name": "for-statement.js", - "end": [ - 1, - 28 - ] - }, - { - "start": [ - 1, - 25 - ], - "name": "for-statement.js", - "end": [ - 1, - 27 - ] - } - ] - }, - "summary": "Replaced '100' with '10'", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "for-statement.js" - ], - "sha1": "f4a0a3f223f66ace49c2e2894579639324035b85", - "gitDir": "test/corpus/repos/javascript", - "sha2": "b7aa4657257e1ff7e9018ca951c22d9c08f4ca5b" -} -,{ - "testCaseDescription": "javascript-for-statement-replacement-test", - "expectedResult": { - "changes": { - "for-statement.js": [ - { - "span": { - "these": [ - { - "start": [ - 1, - 25 - ], - "name": "for-statement.js", - "end": [ - 1, - 27 - ] - }, - { - "start": [ - 1, - 25 - ], - "name": "for-statement.js", - "end": [ - 1, - 28 - ] - } - ] - }, - "summary": "Replaced '10' with '100'", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "for-statement.js" - ], - "sha1": "b7aa4657257e1ff7e9018ca951c22d9c08f4ca5b", - "gitDir": "test/corpus/repos/javascript", - "sha2": "d90fd03838f2ae92733c5d13db56c51f4dded714" -} -,{ - "testCaseDescription": "javascript-for-statement-delete-replacement-test", - "expectedResult": { - "changes": { - "for-statement.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "for-statement.js", - "end": [ - 1, - 46 - ] - } - }, - "summary": "Deleted the 'i = 0, init(); i < 100; i++' for statement", - "tag": "JSONSummary" - }, - { - "span": { - "this": { - "start": [ - 2, - 1 - ], - "name": "for-statement.js", - "end": [ - 2, - 45 - ] - } - }, - "summary": "Deleted the 'i = 0, init(); i < 10; i++' for statement", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "for-statement.js", - "end": [ - 2, - 46 - ] - } - }, - "summary": "Added the 'i = 0, init(); i < 100; i++' for statement", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "for-statement.js" - ], - "sha1": "d90fd03838f2ae92733c5d13db56c51f4dded714", - "gitDir": "test/corpus/repos/javascript", - "sha2": "6a61a685e17ba55bf3982bab2b696346df632862" -} -,{ - "testCaseDescription": "javascript-for-statement-delete-test", - "expectedResult": { - "changes": { - "for-statement.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "for-statement.js", - "end": [ - 1, - 45 - ] - } - }, - "summary": "Deleted the 'i = 0, init(); i < 10; i++' for statement", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "for-statement.js" - ], - "sha1": "6a61a685e17ba55bf3982bab2b696346df632862", - "gitDir": "test/corpus/repos/javascript", - "sha2": "2bdadc3ac8ea4e15f6f2d7b4a9d1d2cf3b0a9567" -} -,{ - "testCaseDescription": "javascript-for-statement-delete-rest-test", - "expectedResult": { - "changes": { - "for-statement.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "for-statement.js", - "end": [ - 1, - 46 - ] - } - }, - "summary": "Deleted the 'i = 0, init(); i < 100; i++' for statement", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "for-statement.js" - ], - "sha1": "2bdadc3ac8ea4e15f6f2d7b4a9d1d2cf3b0a9567", - "gitDir": "test/corpus/repos/javascript", - "sha2": "e66aa2b6bacc2bbd796427540227b298518b1389" -}] diff --git a/test/corpus/diff-summaries/javascript/function-call-args.json b/test/corpus/diff-summaries/javascript/function-call-args.json deleted file mode 100644 index 3a990747e..000000000 --- a/test/corpus/diff-summaries/javascript/function-call-args.json +++ /dev/null @@ -1,608 +0,0 @@ -[{ - "testCaseDescription": "javascript-function-call-args-insert-test", - "expectedResult": { - "changes": { - "function-call-args.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "function-call-args.js", - "end": [ - 1, - 77 - ] - } - }, - "summary": "Added the 'someFunction(1, \"string\", …, true)' function call", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "function-call-args.js" - ], - "sha1": "101b21dd5ae54a69443d6899a30f575b0500e085", - "gitDir": "test/corpus/repos/javascript", - "sha2": "0dc5c6df87d1ae60a9b4195126f2b0c70eecfc6e" -} -,{ - "testCaseDescription": "javascript-function-call-args-replacement-insert-test", - "expectedResult": { - "changes": { - "function-call-args.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "function-call-args.js", - "end": [ - 1, - 83 - ] - } - }, - "summary": "Added the 'someFunction(1, \"otherString\", …, false)' function call", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "function-call-args.js", - "end": [ - 2, - 77 - ] - } - }, - "summary": "Added the 'someFunction(1, \"string\", …, true)' function call", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "function-call-args.js" - ], - "sha1": "0dc5c6df87d1ae60a9b4195126f2b0c70eecfc6e", - "gitDir": "test/corpus/repos/javascript", - "sha2": "a10b3fa59ae8e50c1c0d6bc1a341eb31b41c6a9f" -} -,{ - "testCaseDescription": "javascript-function-call-args-delete-insert-test", - "expectedResult": { - "changes": { - "function-call-args.js": [ - { - "span": { - "these": [ - { - "start": [ - 1, - 17 - ], - "name": "function-call-args.js", - "end": [ - 1, - 30 - ] - }, - { - "start": [ - 1, - 17 - ], - "name": "function-call-args.js", - "end": [ - 1, - 25 - ] - } - ] - }, - "summary": "Replaced the \"otherString\" string with the \"string\" string in the someFunction(1, \"string\", …, true) function call", - "tag": "JSONSummary" - }, - { - "span": { - "these": [ - { - "start": [ - 1, - 41 - ], - "name": "function-call-args.js", - "end": [ - 1, - 42 - ] - }, - { - "start": [ - 1, - 36 - ], - "name": "function-call-args.js", - "end": [ - 1, - 37 - ] - } - ] - }, - "summary": "Replaced the 'b' identifier with the 'a' identifier in the someFunction(1, \"string\", …, true) function call", - "tag": "JSONSummary" - }, - { - "span": { - "these": [ - { - "start": [ - 1, - 43 - ], - "name": "function-call-args.js", - "end": [ - 1, - 44 - ] - }, - { - "start": [ - 1, - 38 - ], - "name": "function-call-args.js", - "end": [ - 1, - 39 - ] - } - ] - }, - "summary": "Replaced the 'c' identifier with the 'b' identifier in the someFunction(1, \"string\", …, true) function call", - "tag": "JSONSummary" - }, - { - "span": { - "these": [ - { - "start": [ - 1, - 60 - ], - "name": "function-call-args.js", - "end": [ - 1, - 61 - ] - }, - { - "start": [ - 1, - 55 - ], - "name": "function-call-args.js", - "end": [ - 1, - 56 - ] - } - ] - }, - "summary": "Replaced the 'b' identifier with the 'a' identifier in the console.log(a) method call", - "tag": "JSONSummary" - }, - { - "span": { - "these": [ - { - "start": [ - 1, - 71 - ], - "name": "function-call-args.js", - "end": [ - 1, - 72 - ] - }, - { - "start": [ - 1, - 66 - ], - "name": "function-call-args.js", - "end": [ - 1, - 67 - ] - } - ] - }, - "summary": "Replaced the 'c' identifier with the 'b' identifier in the someFunction(1, \"string\", …, true) function call", - "tag": "JSONSummary" - }, - { - "span": { - "these": [ - { - "start": [ - 1, - 77 - ], - "name": "function-call-args.js", - "end": [ - 1, - 82 - ] - }, - { - "start": [ - 1, - 72 - ], - "name": "function-call-args.js", - "end": [ - 1, - 76 - ] - } - ] - }, - "summary": "Replaced 'false' with 'true' in the someFunction(1, \"string\", …, true) function call", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "function-call-args.js" - ], - "sha1": "a10b3fa59ae8e50c1c0d6bc1a341eb31b41c6a9f", - "gitDir": "test/corpus/repos/javascript", - "sha2": "940f6218f550757ae9d53a05ffe7d1893ceb085a" -} -,{ - "testCaseDescription": "javascript-function-call-args-replacement-test", - "expectedResult": { - "changes": { - "function-call-args.js": [ - { - "span": { - "these": [ - { - "start": [ - 1, - 17 - ], - "name": "function-call-args.js", - "end": [ - 1, - 25 - ] - }, - { - "start": [ - 1, - 17 - ], - "name": "function-call-args.js", - "end": [ - 1, - 30 - ] - } - ] - }, - "summary": "Replaced the \"string\" string with the \"otherString\" string in the someFunction(1, \"otherString\", …, false) function call", - "tag": "JSONSummary" - }, - { - "span": { - "these": [ - { - "start": [ - 1, - 36 - ], - "name": "function-call-args.js", - "end": [ - 1, - 37 - ] - }, - { - "start": [ - 1, - 41 - ], - "name": "function-call-args.js", - "end": [ - 1, - 42 - ] - } - ] - }, - "summary": "Replaced the 'a' identifier with the 'b' identifier in the someFunction(1, \"otherString\", …, false) function call", - "tag": "JSONSummary" - }, - { - "span": { - "these": [ - { - "start": [ - 1, - 38 - ], - "name": "function-call-args.js", - "end": [ - 1, - 39 - ] - }, - { - "start": [ - 1, - 43 - ], - "name": "function-call-args.js", - "end": [ - 1, - 44 - ] - } - ] - }, - "summary": "Replaced the 'b' identifier with the 'c' identifier in the someFunction(1, \"otherString\", …, false) function call", - "tag": "JSONSummary" - }, - { - "span": { - "these": [ - { - "start": [ - 1, - 55 - ], - "name": "function-call-args.js", - "end": [ - 1, - 56 - ] - }, - { - "start": [ - 1, - 60 - ], - "name": "function-call-args.js", - "end": [ - 1, - 61 - ] - } - ] - }, - "summary": "Replaced the 'a' identifier with the 'b' identifier in the console.log(b) method call", - "tag": "JSONSummary" - }, - { - "span": { - "these": [ - { - "start": [ - 1, - 66 - ], - "name": "function-call-args.js", - "end": [ - 1, - 67 - ] - }, - { - "start": [ - 1, - 71 - ], - "name": "function-call-args.js", - "end": [ - 1, - 72 - ] - } - ] - }, - "summary": "Replaced the 'b' identifier with the 'c' identifier in the someFunction(1, \"otherString\", …, false) function call", - "tag": "JSONSummary" - }, - { - "span": { - "these": [ - { - "start": [ - 1, - 72 - ], - "name": "function-call-args.js", - "end": [ - 1, - 76 - ] - }, - { - "start": [ - 1, - 77 - ], - "name": "function-call-args.js", - "end": [ - 1, - 82 - ] - } - ] - }, - "summary": "Replaced 'true' with 'false' in the someFunction(1, \"otherString\", …, false) function call", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "function-call-args.js" - ], - "sha1": "940f6218f550757ae9d53a05ffe7d1893ceb085a", - "gitDir": "test/corpus/repos/javascript", - "sha2": "7efa824b428048d98a2183fb8704105e37e8ac6e" -} -,{ - "testCaseDescription": "javascript-function-call-args-delete-replacement-test", - "expectedResult": { - "changes": { - "function-call-args.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "function-call-args.js", - "end": [ - 1, - 83 - ] - } - }, - "summary": "Deleted the 'someFunction(1, \"otherString\", …, false)' function call", - "tag": "JSONSummary" - }, - { - "span": { - "this": { - "start": [ - 2, - 1 - ], - "name": "function-call-args.js", - "end": [ - 2, - 77 - ] - } - }, - "summary": "Deleted the 'someFunction(1, \"string\", …, true)' function call", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "function-call-args.js", - "end": [ - 2, - 83 - ] - } - }, - "summary": "Added the 'someFunction(1, \"otherString\", …, false)' function call", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "function-call-args.js" - ], - "sha1": "7efa824b428048d98a2183fb8704105e37e8ac6e", - "gitDir": "test/corpus/repos/javascript", - "sha2": "375b6403b1b7e5fe2c26b799eeb8a097ae63c749" -} -,{ - "testCaseDescription": "javascript-function-call-args-delete-test", - "expectedResult": { - "changes": { - "function-call-args.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "function-call-args.js", - "end": [ - 1, - 77 - ] - } - }, - "summary": "Deleted the 'someFunction(1, \"string\", …, true)' function call", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "function-call-args.js" - ], - "sha1": "375b6403b1b7e5fe2c26b799eeb8a097ae63c749", - "gitDir": "test/corpus/repos/javascript", - "sha2": "62375666f152e860d0bdffdb49dcb981c5e77a1e" -} -,{ - "testCaseDescription": "javascript-function-call-args-delete-rest-test", - "expectedResult": { - "changes": { - "function-call-args.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "function-call-args.js", - "end": [ - 1, - 83 - ] - } - }, - "summary": "Deleted the 'someFunction(1, \"otherString\", …, false)' function call", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "function-call-args.js" - ], - "sha1": "62375666f152e860d0bdffdb49dcb981c5e77a1e", - "gitDir": "test/corpus/repos/javascript", - "sha2": "e5315f0371489f42d527c318faa1406833bb3c86" -}] diff --git a/test/corpus/diff-summaries/javascript/function-call.json b/test/corpus/diff-summaries/javascript/function-call.json deleted file mode 100644 index a569ce162..000000000 --- a/test/corpus/diff-summaries/javascript/function-call.json +++ /dev/null @@ -1,308 +0,0 @@ -[{ - "testCaseDescription": "javascript-function-call-insert-test", - "expectedResult": { - "changes": { - "function-call.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "function-call.js", - "end": [ - 1, - 27 - ] - } - }, - "summary": "Added the 'someFunction(arg1, \"arg2\")' function call", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "function-call.js" - ], - "sha1": "cf31ddf834d011d1d55eee3da85c70f15eea67f1", - "gitDir": "test/corpus/repos/javascript", - "sha2": "67d53107901a801fcd3027e5e0e5aae18fb2ca36" -} -,{ - "testCaseDescription": "javascript-function-call-replacement-insert-test", - "expectedResult": { - "changes": { - "function-call.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "function-call.js", - "end": [ - 1, - 27 - ] - } - }, - "summary": "Added the 'someFunction(arg1, \"arg3\")' function call", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "function-call.js", - "end": [ - 2, - 27 - ] - } - }, - "summary": "Added the 'someFunction(arg1, \"arg2\")' function call", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "function-call.js" - ], - "sha1": "67d53107901a801fcd3027e5e0e5aae18fb2ca36", - "gitDir": "test/corpus/repos/javascript", - "sha2": "211596a53308346f468fe8ed76ace3ce30ddf4da" -} -,{ - "testCaseDescription": "javascript-function-call-delete-insert-test", - "expectedResult": { - "changes": { - "function-call.js": [ - { - "span": { - "these": [ - { - "start": [ - 1, - 20 - ], - "name": "function-call.js", - "end": [ - 1, - 26 - ] - }, - { - "start": [ - 1, - 20 - ], - "name": "function-call.js", - "end": [ - 1, - 26 - ] - } - ] - }, - "summary": "Replaced the \"arg3\" string with the \"arg2\" string in the someFunction(arg1, \"arg2\") function call", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "function-call.js" - ], - "sha1": "211596a53308346f468fe8ed76ace3ce30ddf4da", - "gitDir": "test/corpus/repos/javascript", - "sha2": "fd80aa4f89fad9074132808237e195a8d9545b86" -} -,{ - "testCaseDescription": "javascript-function-call-replacement-test", - "expectedResult": { - "changes": { - "function-call.js": [ - { - "span": { - "these": [ - { - "start": [ - 1, - 20 - ], - "name": "function-call.js", - "end": [ - 1, - 26 - ] - }, - { - "start": [ - 1, - 20 - ], - "name": "function-call.js", - "end": [ - 1, - 26 - ] - } - ] - }, - "summary": "Replaced the \"arg2\" string with the \"arg3\" string in the someFunction(arg1, \"arg3\") function call", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "function-call.js" - ], - "sha1": "fd80aa4f89fad9074132808237e195a8d9545b86", - "gitDir": "test/corpus/repos/javascript", - "sha2": "9f9c596f918e7d7c6a538e6213855683eccd9dd7" -} -,{ - "testCaseDescription": "javascript-function-call-delete-replacement-test", - "expectedResult": { - "changes": { - "function-call.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "function-call.js", - "end": [ - 1, - 27 - ] - } - }, - "summary": "Deleted the 'someFunction(arg1, \"arg3\")' function call", - "tag": "JSONSummary" - }, - { - "span": { - "this": { - "start": [ - 2, - 1 - ], - "name": "function-call.js", - "end": [ - 2, - 27 - ] - } - }, - "summary": "Deleted the 'someFunction(arg1, \"arg2\")' function call", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "function-call.js", - "end": [ - 2, - 27 - ] - } - }, - "summary": "Added the 'someFunction(arg1, \"arg3\")' function call", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "function-call.js" - ], - "sha1": "9f9c596f918e7d7c6a538e6213855683eccd9dd7", - "gitDir": "test/corpus/repos/javascript", - "sha2": "044ad612c7ddae2a92516fa81c38fe337f45f44b" -} -,{ - "testCaseDescription": "javascript-function-call-delete-test", - "expectedResult": { - "changes": { - "function-call.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "function-call.js", - "end": [ - 1, - 27 - ] - } - }, - "summary": "Deleted the 'someFunction(arg1, \"arg2\")' function call", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "function-call.js" - ], - "sha1": "044ad612c7ddae2a92516fa81c38fe337f45f44b", - "gitDir": "test/corpus/repos/javascript", - "sha2": "245fd4ed85aa4fbcecaca43247ca77efa8382c34" -} -,{ - "testCaseDescription": "javascript-function-call-delete-rest-test", - "expectedResult": { - "changes": { - "function-call.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "function-call.js", - "end": [ - 1, - 27 - ] - } - }, - "summary": "Deleted the 'someFunction(arg1, \"arg3\")' function call", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "function-call.js" - ], - "sha1": "245fd4ed85aa4fbcecaca43247ca77efa8382c34", - "gitDir": "test/corpus/repos/javascript", - "sha2": "1057513972364b1ca48ee19f74fb73ca06119e8c" -}] diff --git a/test/corpus/diff-summaries/javascript/function.json b/test/corpus/diff-summaries/javascript/function.json deleted file mode 100644 index 54a3fe590..000000000 --- a/test/corpus/diff-summaries/javascript/function.json +++ /dev/null @@ -1,308 +0,0 @@ -[{ - "testCaseDescription": "javascript-function-insert-test", - "expectedResult": { - "changes": { - "function.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "function.js", - "end": [ - 1, - 31 - ] - } - }, - "summary": "Added an anonymous(arg1, arg2) function", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "function.js" - ], - "sha1": "492ece78ac243f74d0f0bfce83c94b7162c1eaa6", - "gitDir": "test/corpus/repos/javascript", - "sha2": "a1e7c18328813b605f462f8909d48f17a8e0143b" -} -,{ - "testCaseDescription": "javascript-function-replacement-insert-test", - "expectedResult": { - "changes": { - "function.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "function.js", - "end": [ - 1, - 31 - ] - } - }, - "summary": "Added an anonymous(arg1, arg2) function", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "function.js", - "end": [ - 2, - 31 - ] - } - }, - "summary": "Added an anonymous(arg1, arg2) function", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "function.js" - ], - "sha1": "a1e7c18328813b605f462f8909d48f17a8e0143b", - "gitDir": "test/corpus/repos/javascript", - "sha2": "2bf863a59e774f4350a3cdd80cf5dc5a491b7c7c" -} -,{ - "testCaseDescription": "javascript-function-delete-insert-test", - "expectedResult": { - "changes": { - "function.js": [ - { - "span": { - "these": [ - { - "start": [ - 1, - 24 - ], - "name": "function.js", - "end": [ - 1, - 28 - ] - }, - { - "start": [ - 1, - 24 - ], - "name": "function.js", - "end": [ - 1, - 28 - ] - } - ] - }, - "summary": "Replaced the 'arg1' identifier with the 'arg2' identifier", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "function.js" - ], - "sha1": "2bf863a59e774f4350a3cdd80cf5dc5a491b7c7c", - "gitDir": "test/corpus/repos/javascript", - "sha2": "ccdde180a122687c848a953946552ab2e0e85f19" -} -,{ - "testCaseDescription": "javascript-function-replacement-test", - "expectedResult": { - "changes": { - "function.js": [ - { - "span": { - "these": [ - { - "start": [ - 1, - 24 - ], - "name": "function.js", - "end": [ - 1, - 28 - ] - }, - { - "start": [ - 1, - 24 - ], - "name": "function.js", - "end": [ - 1, - 28 - ] - } - ] - }, - "summary": "Replaced the 'arg2' identifier with the 'arg1' identifier", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "function.js" - ], - "sha1": "ccdde180a122687c848a953946552ab2e0e85f19", - "gitDir": "test/corpus/repos/javascript", - "sha2": "2fc4cc2b1dd48ca880339b2e7bdcb80aa8474eab" -} -,{ - "testCaseDescription": "javascript-function-delete-replacement-test", - "expectedResult": { - "changes": { - "function.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "function.js", - "end": [ - 1, - 31 - ] - } - }, - "summary": "Deleted an anonymous(arg1, arg2) function", - "tag": "JSONSummary" - }, - { - "span": { - "this": { - "start": [ - 2, - 1 - ], - "name": "function.js", - "end": [ - 2, - 31 - ] - } - }, - "summary": "Deleted an anonymous(arg1, arg2) function", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "function.js", - "end": [ - 2, - 31 - ] - } - }, - "summary": "Added an anonymous(arg1, arg2) function", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "function.js" - ], - "sha1": "2fc4cc2b1dd48ca880339b2e7bdcb80aa8474eab", - "gitDir": "test/corpus/repos/javascript", - "sha2": "265e835586016a3afaf60e97b0953a0e63a5908c" -} -,{ - "testCaseDescription": "javascript-function-delete-test", - "expectedResult": { - "changes": { - "function.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "function.js", - "end": [ - 1, - 31 - ] - } - }, - "summary": "Deleted an anonymous(arg1, arg2) function", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "function.js" - ], - "sha1": "265e835586016a3afaf60e97b0953a0e63a5908c", - "gitDir": "test/corpus/repos/javascript", - "sha2": "9a2c09c340bccbd2ea80dbf353014da199f45840" -} -,{ - "testCaseDescription": "javascript-function-delete-rest-test", - "expectedResult": { - "changes": { - "function.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "function.js", - "end": [ - 1, - 31 - ] - } - }, - "summary": "Deleted an anonymous(arg1, arg2) function", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "function.js" - ], - "sha1": "9a2c09c340bccbd2ea80dbf353014da199f45840", - "gitDir": "test/corpus/repos/javascript", - "sha2": "142158e6e72a9a884b0d89c0b044b5c1473248db" -}] diff --git a/test/corpus/diff-summaries/javascript/generator-function.json b/test/corpus/diff-summaries/javascript/generator-function.json deleted file mode 100644 index f9294a434..000000000 --- a/test/corpus/diff-summaries/javascript/generator-function.json +++ /dev/null @@ -1,308 +0,0 @@ -[{ - "testCaseDescription": "javascript-generator-function-insert-test", - "expectedResult": { - "changes": { - "generator-function.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "generator-function.js", - "end": [ - 1, - 59 - ] - } - }, - "summary": "Added the 'generateStuff' function", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "generator-function.js" - ], - "sha1": "304e0c432994c642daa18c284f4c1578416e77e1", - "gitDir": "test/corpus/repos/javascript", - "sha2": "a1f2e1505ff20196ae782ad0d4c5001bc2cc8cb1" -} -,{ - "testCaseDescription": "javascript-generator-function-replacement-insert-test", - "expectedResult": { - "changes": { - "generator-function.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "generator-function.js", - "end": [ - 1, - 62 - ] - } - }, - "summary": "Added the 'generateNewStuff' function", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "generator-function.js", - "end": [ - 2, - 59 - ] - } - }, - "summary": "Added the 'generateStuff' function", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "generator-function.js" - ], - "sha1": "a1f2e1505ff20196ae782ad0d4c5001bc2cc8cb1", - "gitDir": "test/corpus/repos/javascript", - "sha2": "b4ca6466eb43270aca0908d03a0185180dc75011" -} -,{ - "testCaseDescription": "javascript-generator-function-delete-insert-test", - "expectedResult": { - "changes": { - "generator-function.js": [ - { - "span": { - "these": [ - { - "start": [ - 1, - 11 - ], - "name": "generator-function.js", - "end": [ - 1, - 27 - ] - }, - { - "start": [ - 1, - 11 - ], - "name": "generator-function.js", - "end": [ - 1, - 24 - ] - } - ] - }, - "summary": "Replaced the 'generateNewStuff' identifier with the 'generateStuff' identifier in the generateStuff function", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "generator-function.js" - ], - "sha1": "b4ca6466eb43270aca0908d03a0185180dc75011", - "gitDir": "test/corpus/repos/javascript", - "sha2": "c3a19c5bd3d78102ef15c6a49e8063940d9511ee" -} -,{ - "testCaseDescription": "javascript-generator-function-replacement-test", - "expectedResult": { - "changes": { - "generator-function.js": [ - { - "span": { - "these": [ - { - "start": [ - 1, - 11 - ], - "name": "generator-function.js", - "end": [ - 1, - 24 - ] - }, - { - "start": [ - 1, - 11 - ], - "name": "generator-function.js", - "end": [ - 1, - 27 - ] - } - ] - }, - "summary": "Replaced the 'generateStuff' identifier with the 'generateNewStuff' identifier in the generateNewStuff function", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "generator-function.js" - ], - "sha1": "c3a19c5bd3d78102ef15c6a49e8063940d9511ee", - "gitDir": "test/corpus/repos/javascript", - "sha2": "1d4670fa514b6e44c62cabb9de4cd8c565ac04ee" -} -,{ - "testCaseDescription": "javascript-generator-function-delete-replacement-test", - "expectedResult": { - "changes": { - "generator-function.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "generator-function.js", - "end": [ - 1, - 62 - ] - } - }, - "summary": "Deleted the 'generateNewStuff' function", - "tag": "JSONSummary" - }, - { - "span": { - "this": { - "start": [ - 2, - 1 - ], - "name": "generator-function.js", - "end": [ - 2, - 59 - ] - } - }, - "summary": "Deleted the 'generateStuff' function", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "generator-function.js", - "end": [ - 2, - 62 - ] - } - }, - "summary": "Added the 'generateNewStuff' function", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "generator-function.js" - ], - "sha1": "1d4670fa514b6e44c62cabb9de4cd8c565ac04ee", - "gitDir": "test/corpus/repos/javascript", - "sha2": "a3f49a301897c265545ecb113bfdc96850ca29f1" -} -,{ - "testCaseDescription": "javascript-generator-function-delete-test", - "expectedResult": { - "changes": { - "generator-function.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "generator-function.js", - "end": [ - 1, - 59 - ] - } - }, - "summary": "Deleted the 'generateStuff' function", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "generator-function.js" - ], - "sha1": "a3f49a301897c265545ecb113bfdc96850ca29f1", - "gitDir": "test/corpus/repos/javascript", - "sha2": "6d10fc13004f3500329c6bbae82678004ac0a103" -} -,{ - "testCaseDescription": "javascript-generator-function-delete-rest-test", - "expectedResult": { - "changes": { - "generator-function.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "generator-function.js", - "end": [ - 1, - 62 - ] - } - }, - "summary": "Deleted the 'generateNewStuff' function", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "generator-function.js" - ], - "sha1": "6d10fc13004f3500329c6bbae82678004ac0a103", - "gitDir": "test/corpus/repos/javascript", - "sha2": "2f00ecb14d10a4cc210b7a56309fc75db90f3b64" -}] diff --git a/test/corpus/diff-summaries/javascript/identifier.json b/test/corpus/diff-summaries/javascript/identifier.json deleted file mode 100644 index 25f05ec96..000000000 --- a/test/corpus/diff-summaries/javascript/identifier.json +++ /dev/null @@ -1,308 +0,0 @@ -[{ - "testCaseDescription": "javascript-identifier-insert-test", - "expectedResult": { - "changes": { - "identifier.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "identifier.js", - "end": [ - 1, - 7 - ] - } - }, - "summary": "Added the 'theVar' identifier", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "identifier.js" - ], - "sha1": "e117ae3f5e0945e0d8e971f7bbc0397229a45648", - "gitDir": "test/corpus/repos/javascript", - "sha2": "0e588d86e85373e48c2f0698ec1f04561b9a24e2" -} -,{ - "testCaseDescription": "javascript-identifier-replacement-insert-test", - "expectedResult": { - "changes": { - "identifier.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "identifier.js", - "end": [ - 1, - 8 - ] - } - }, - "summary": "Added the 'theVar2' identifier", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "identifier.js", - "end": [ - 2, - 7 - ] - } - }, - "summary": "Added the 'theVar' identifier", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "identifier.js" - ], - "sha1": "0e588d86e85373e48c2f0698ec1f04561b9a24e2", - "gitDir": "test/corpus/repos/javascript", - "sha2": "304194727ea2932362b0d03d8f79a362974303ad" -} -,{ - "testCaseDescription": "javascript-identifier-delete-insert-test", - "expectedResult": { - "changes": { - "identifier.js": [ - { - "span": { - "these": [ - { - "start": [ - 1, - 1 - ], - "name": "identifier.js", - "end": [ - 1, - 8 - ] - }, - { - "start": [ - 1, - 1 - ], - "name": "identifier.js", - "end": [ - 1, - 7 - ] - } - ] - }, - "summary": "Replaced the 'theVar2' identifier with the 'theVar' identifier", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "identifier.js" - ], - "sha1": "304194727ea2932362b0d03d8f79a362974303ad", - "gitDir": "test/corpus/repos/javascript", - "sha2": "17438bcefeb350651ad9c920c65e6b8d21f3c157" -} -,{ - "testCaseDescription": "javascript-identifier-replacement-test", - "expectedResult": { - "changes": { - "identifier.js": [ - { - "span": { - "these": [ - { - "start": [ - 1, - 1 - ], - "name": "identifier.js", - "end": [ - 1, - 7 - ] - }, - { - "start": [ - 1, - 1 - ], - "name": "identifier.js", - "end": [ - 1, - 8 - ] - } - ] - }, - "summary": "Replaced the 'theVar' identifier with the 'theVar2' identifier", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "identifier.js" - ], - "sha1": "17438bcefeb350651ad9c920c65e6b8d21f3c157", - "gitDir": "test/corpus/repos/javascript", - "sha2": "db1afa5037ec331c9d2a490ec2c6052ed06235f8" -} -,{ - "testCaseDescription": "javascript-identifier-delete-replacement-test", - "expectedResult": { - "changes": { - "identifier.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "identifier.js", - "end": [ - 1, - 8 - ] - } - }, - "summary": "Deleted the 'theVar2' identifier", - "tag": "JSONSummary" - }, - { - "span": { - "this": { - "start": [ - 2, - 1 - ], - "name": "identifier.js", - "end": [ - 2, - 7 - ] - } - }, - "summary": "Deleted the 'theVar' identifier", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "identifier.js", - "end": [ - 2, - 8 - ] - } - }, - "summary": "Added the 'theVar2' identifier", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "identifier.js" - ], - "sha1": "db1afa5037ec331c9d2a490ec2c6052ed06235f8", - "gitDir": "test/corpus/repos/javascript", - "sha2": "ab62284a2d89f526cdde80ad60e4f448a2376bed" -} -,{ - "testCaseDescription": "javascript-identifier-delete-test", - "expectedResult": { - "changes": { - "identifier.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "identifier.js", - "end": [ - 1, - 7 - ] - } - }, - "summary": "Deleted the 'theVar' identifier", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "identifier.js" - ], - "sha1": "ab62284a2d89f526cdde80ad60e4f448a2376bed", - "gitDir": "test/corpus/repos/javascript", - "sha2": "063615a0cbe20132f23e2f4ec74c4c10658840c6" -} -,{ - "testCaseDescription": "javascript-identifier-delete-rest-test", - "expectedResult": { - "changes": { - "identifier.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "identifier.js", - "end": [ - 1, - 8 - ] - } - }, - "summary": "Deleted the 'theVar2' identifier", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "identifier.js" - ], - "sha1": "063615a0cbe20132f23e2f4ec74c4c10658840c6", - "gitDir": "test/corpus/repos/javascript", - "sha2": "ebab90bd29d724f6dda4d39a32a6fa7d0b9adf52" -}] diff --git a/test/corpus/diff-summaries/javascript/if-else.json b/test/corpus/diff-summaries/javascript/if-else.json deleted file mode 100644 index 651c3ca00..000000000 --- a/test/corpus/diff-summaries/javascript/if-else.json +++ /dev/null @@ -1,308 +0,0 @@ -[{ - "testCaseDescription": "javascript-if-else-insert-test", - "expectedResult": { - "changes": { - "if-else.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "if-else.js", - "end": [ - 1, - 25 - ] - } - }, - "summary": "Added the 'x' if statement", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "if-else.js" - ], - "sha1": "805427c7aaf71a887c429562b647fe6811ba39c9", - "gitDir": "test/corpus/repos/javascript", - "sha2": "46ab86718f54c48cd2f565a432f4187de5bc0fbe" -} -,{ - "testCaseDescription": "javascript-if-else-replacement-insert-test", - "expectedResult": { - "changes": { - "if-else.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "if-else.js", - "end": [ - 1, - 29 - ] - } - }, - "summary": "Added the 'a' if statement", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "if-else.js", - "end": [ - 2, - 25 - ] - } - }, - "summary": "Added the 'x' if statement", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "if-else.js" - ], - "sha1": "46ab86718f54c48cd2f565a432f4187de5bc0fbe", - "gitDir": "test/corpus/repos/javascript", - "sha2": "111b0fa6c30be41e42f49a8b97734c2f29ffe887" -} -,{ - "testCaseDescription": "javascript-if-else-delete-insert-test", - "expectedResult": { - "changes": { - "if-else.js": [ - { - "span": { - "these": [ - { - "start": [ - 1, - 1 - ], - "name": "if-else.js", - "end": [ - 1, - 29 - ] - }, - { - "start": [ - 1, - 1 - ], - "name": "if-else.js", - "end": [ - 1, - 25 - ] - } - ] - }, - "summary": "Replaced the 'a' if statement with the 'x' if statement", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "if-else.js" - ], - "sha1": "111b0fa6c30be41e42f49a8b97734c2f29ffe887", - "gitDir": "test/corpus/repos/javascript", - "sha2": "86bcc1f27f5c8d1108c1fd41681db0786ce40577" -} -,{ - "testCaseDescription": "javascript-if-else-replacement-test", - "expectedResult": { - "changes": { - "if-else.js": [ - { - "span": { - "these": [ - { - "start": [ - 1, - 1 - ], - "name": "if-else.js", - "end": [ - 1, - 25 - ] - }, - { - "start": [ - 1, - 1 - ], - "name": "if-else.js", - "end": [ - 1, - 29 - ] - } - ] - }, - "summary": "Replaced the 'x' if statement with the 'a' if statement", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "if-else.js" - ], - "sha1": "86bcc1f27f5c8d1108c1fd41681db0786ce40577", - "gitDir": "test/corpus/repos/javascript", - "sha2": "08b8b6246b046b2fa0a5b480bde9ea2a59496cab" -} -,{ - "testCaseDescription": "javascript-if-else-delete-replacement-test", - "expectedResult": { - "changes": { - "if-else.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "if-else.js", - "end": [ - 1, - 29 - ] - } - }, - "summary": "Deleted the 'a' if statement", - "tag": "JSONSummary" - }, - { - "span": { - "this": { - "start": [ - 2, - 1 - ], - "name": "if-else.js", - "end": [ - 2, - 25 - ] - } - }, - "summary": "Deleted the 'x' if statement", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "if-else.js", - "end": [ - 2, - 29 - ] - } - }, - "summary": "Added the 'a' if statement", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "if-else.js" - ], - "sha1": "08b8b6246b046b2fa0a5b480bde9ea2a59496cab", - "gitDir": "test/corpus/repos/javascript", - "sha2": "f3c6acb380e4f8baa60d7ea87e7d62bdfb6832ac" -} -,{ - "testCaseDescription": "javascript-if-else-delete-test", - "expectedResult": { - "changes": { - "if-else.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "if-else.js", - "end": [ - 1, - 25 - ] - } - }, - "summary": "Deleted the 'x' if statement", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "if-else.js" - ], - "sha1": "f3c6acb380e4f8baa60d7ea87e7d62bdfb6832ac", - "gitDir": "test/corpus/repos/javascript", - "sha2": "542ca4c9f7fdfd3e4660588a20f5cc7f40792166" -} -,{ - "testCaseDescription": "javascript-if-else-delete-rest-test", - "expectedResult": { - "changes": { - "if-else.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "if-else.js", - "end": [ - 1, - 29 - ] - } - }, - "summary": "Deleted the 'a' if statement", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "if-else.js" - ], - "sha1": "542ca4c9f7fdfd3e4660588a20f5cc7f40792166", - "gitDir": "test/corpus/repos/javascript", - "sha2": "125f2e2e8e65a10784e72bb113319c805d4f42ac" -}] diff --git a/test/corpus/diff-summaries/javascript/if.json b/test/corpus/diff-summaries/javascript/if.json deleted file mode 100644 index 05a82ecd3..000000000 --- a/test/corpus/diff-summaries/javascript/if.json +++ /dev/null @@ -1,308 +0,0 @@ -[{ - "testCaseDescription": "javascript-if-insert-test", - "expectedResult": { - "changes": { - "if.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "if.js", - "end": [ - 1, - 19 - ] - } - }, - "summary": "Added the 'x' if statement", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "if.js" - ], - "sha1": "408411b4e79d51cf3b50541c8d1115a3ce46dfa8", - "gitDir": "test/corpus/repos/javascript", - "sha2": "66188f5ab8580e98c37f0b8702e95544551be755" -} -,{ - "testCaseDescription": "javascript-if-replacement-insert-test", - "expectedResult": { - "changes": { - "if.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "if.js", - "end": [ - 1, - 24 - ] - } - }, - "summary": "Added the 'a.b' if statement", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "if.js", - "end": [ - 2, - 19 - ] - } - }, - "summary": "Added the 'x' if statement", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "if.js" - ], - "sha1": "66188f5ab8580e98c37f0b8702e95544551be755", - "gitDir": "test/corpus/repos/javascript", - "sha2": "0293e32d52fc191e4a768a91746259c99acc2342" -} -,{ - "testCaseDescription": "javascript-if-delete-insert-test", - "expectedResult": { - "changes": { - "if.js": [ - { - "span": { - "these": [ - { - "start": [ - 1, - 1 - ], - "name": "if.js", - "end": [ - 1, - 24 - ] - }, - { - "start": [ - 1, - 1 - ], - "name": "if.js", - "end": [ - 1, - 19 - ] - } - ] - }, - "summary": "Replaced the 'a.b' if statement with the 'x' if statement", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "if.js" - ], - "sha1": "0293e32d52fc191e4a768a91746259c99acc2342", - "gitDir": "test/corpus/repos/javascript", - "sha2": "7dd98c9d586de0e61d3b80ac34fe25e4f89cab42" -} -,{ - "testCaseDescription": "javascript-if-replacement-test", - "expectedResult": { - "changes": { - "if.js": [ - { - "span": { - "these": [ - { - "start": [ - 1, - 1 - ], - "name": "if.js", - "end": [ - 1, - 19 - ] - }, - { - "start": [ - 1, - 1 - ], - "name": "if.js", - "end": [ - 1, - 24 - ] - } - ] - }, - "summary": "Replaced the 'x' if statement with the 'a.b' if statement", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "if.js" - ], - "sha1": "7dd98c9d586de0e61d3b80ac34fe25e4f89cab42", - "gitDir": "test/corpus/repos/javascript", - "sha2": "9a8f836a101bdd5418634b5e762b9db21a91011c" -} -,{ - "testCaseDescription": "javascript-if-delete-replacement-test", - "expectedResult": { - "changes": { - "if.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "if.js", - "end": [ - 1, - 24 - ] - } - }, - "summary": "Deleted the 'a.b' if statement", - "tag": "JSONSummary" - }, - { - "span": { - "this": { - "start": [ - 2, - 1 - ], - "name": "if.js", - "end": [ - 2, - 19 - ] - } - }, - "summary": "Deleted the 'x' if statement", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "if.js", - "end": [ - 2, - 24 - ] - } - }, - "summary": "Added the 'a.b' if statement", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "if.js" - ], - "sha1": "9a8f836a101bdd5418634b5e762b9db21a91011c", - "gitDir": "test/corpus/repos/javascript", - "sha2": "179c1b82b833c249afd123f342dfd06380b5acb8" -} -,{ - "testCaseDescription": "javascript-if-delete-test", - "expectedResult": { - "changes": { - "if.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "if.js", - "end": [ - 1, - 19 - ] - } - }, - "summary": "Deleted the 'x' if statement", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "if.js" - ], - "sha1": "179c1b82b833c249afd123f342dfd06380b5acb8", - "gitDir": "test/corpus/repos/javascript", - "sha2": "95123146ceab7cf639e49adb97d36a8556c19940" -} -,{ - "testCaseDescription": "javascript-if-delete-rest-test", - "expectedResult": { - "changes": { - "if.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "if.js", - "end": [ - 1, - 24 - ] - } - }, - "summary": "Deleted the 'a.b' if statement", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "if.js" - ], - "sha1": "95123146ceab7cf639e49adb97d36a8556c19940", - "gitDir": "test/corpus/repos/javascript", - "sha2": "805427c7aaf71a887c429562b647fe6811ba39c9" -}] diff --git a/test/corpus/diff-summaries/javascript/import.json b/test/corpus/diff-summaries/javascript/import.json deleted file mode 100644 index 7b0137fa5..000000000 --- a/test/corpus/diff-summaries/javascript/import.json +++ /dev/null @@ -1,214 +0,0 @@ -[{ - "testCaseDescription": "javascript-import-insert-test", - "expectedResult": { - "changes": { - "import.js": [ - "Added the '\"foo\"' import statement", - "Added the '\"aardvark\"' import statement", - "Added the '\"ant\"' import statement", - "Added the '\"antelope\"' import statement", - "Added the '\"ant-eater\"' import statement", - "Added the '\"anaconda\"' import statement", - "Added the '\"alligator\"' import statement", - "Added the '\"arctic-tern\"' import statement" - ] - }, - "errors": {} - }, - "filePaths": [ - "import.js" - ], - "sha1": "fdbc1266a42600d265109d102da2496e26a9d3f2", - "gitDir": "test/corpus/repos/javascript", - "sha2": "df90633016b5463425deb3d74463cdcc32b76889" -} -,{ - "testCaseDescription": "javascript-import-replacement-insert-test", - "expectedResult": { - "changes": { - "import.js": [ - "Added the '\"babirusa\"' import statement", - "Added the '\"baboon\"' import statement", - "Added the '\"badger\"' import statement", - "Added the '\"bald-eagle\"' import statement", - "Added the '\"bandicoot\"' import statement", - "Added the '\"banteng\"' import statement", - "Added the '\"barbet\"' import statement", - "Added the '\"basilisk\"' import statement", - "Added the '\"foo\"' import statement", - "Added the '\"aardvark\"' import statement", - "Added the '\"ant\"' import statement", - "Added the '\"antelope\"' import statement", - "Added the '\"ant-eater\"' import statement", - "Added the '\"anaconda\"' import statement", - "Added the '\"alligator\"' import statement", - "Added the '\"arctic-tern\"' import statement" - ] - }, - "errors": {} - }, - "filePaths": [ - "import.js" - ], - "sha1": "df90633016b5463425deb3d74463cdcc32b76889", - "gitDir": "test/corpus/repos/javascript", - "sha2": "95c90ad1bea428330d0b62f02e607b4509de89d2" -} -,{ - "testCaseDescription": "javascript-import-delete-insert-test", - "expectedResult": { - "changes": { - "import.js": [ - "Replaced the \"babirusa\" string with the \"foo\" string in the \"foo\" import statement", - "Replaced the \"baboon\" string with the \"aardvark\" string in the \"aardvark\" import statement", - "Replaced the 'otherName' identifier with the 'name' identifier in the \"aardvark\" import statement", - "Replaced the \"badger\" string with the \"ant\" string in the \"ant\" import statement", - "Replaced the 'element' identifier with the 'member' identifier in the \"ant\" import statement", - "Replaced the \"bald-eagle\" string with the \"antelope\" string in the \"antelope\" import statement", - "Replaced the 'element1' identifier with the 'member1' identifier in the \"antelope\" import statement", - "Replaced the 'element2' identifier with the 'member2' identifier in the \"antelope\" import statement", - "Replaced the \"bandicoot\" string with the \"ant-eater\" string in the \"ant-eater\" import statement", - "Replaced the 'element1' identifier with the 'member1' identifier in the \"ant-eater\" import statement", - "Replaced the 'element2' identifier with the 'member2' identifier in the \"ant-eater\" import statement", - "Replaced the 'elementAlias2' identifier with the 'alias2' identifier in the \"ant-eater\" import statement", - "Replaced the \"banteng\" string with the \"anaconda\" string in the \"anaconda\" import statement", - "Replaced the 'element1' identifier with the 'member1' identifier in the \"anaconda\" import statement", - "Replaced the 'element2' identifier with the 'member2' identifier in the \"anaconda\" import statement", - "Replaced the 'elementAlias2' identifier with the 'alias2' identifier in the \"anaconda\" import statement", - "Replaced the \"barbet\" string with the \"alligator\" string in the \"alligator\" import statement", - "Replaced the 'element' identifier with the 'name' identifier in the \"alligator\" import statement", - "Replaced the \"basilisk\" string with the \"arctic-tern\" string in the \"arctic-tern\" import statement" - ] - }, - "errors": {} - }, - "filePaths": [ - "import.js" - ], - "sha1": "95c90ad1bea428330d0b62f02e607b4509de89d2", - "gitDir": "test/corpus/repos/javascript", - "sha2": "e7a974df1ae0a2993d5eeda4edd1b586adffe84f" -} -,{ - "testCaseDescription": "javascript-import-replacement-test", - "expectedResult": { - "changes": { - "import.js": [ - "Replaced the \"foo\" string with the \"babirusa\" string in the \"babirusa\" import statement", - "Replaced the \"aardvark\" string with the \"baboon\" string in the \"baboon\" import statement", - "Replaced the 'name' identifier with the 'otherName' identifier in the \"baboon\" import statement", - "Replaced the \"ant\" string with the \"badger\" string in the \"badger\" import statement", - "Replaced the 'member' identifier with the 'element' identifier in the \"badger\" import statement", - "Replaced the \"antelope\" string with the \"bald-eagle\" string in the \"bald-eagle\" import statement", - "Replaced the 'member1' identifier with the 'element1' identifier in the \"bald-eagle\" import statement", - "Replaced the 'member2' identifier with the 'element2' identifier in the \"bald-eagle\" import statement", - "Replaced the \"ant-eater\" string with the \"bandicoot\" string in the \"bandicoot\" import statement", - "Replaced the 'member1' identifier with the 'element1' identifier in the \"bandicoot\" import statement", - "Replaced the 'member2' identifier with the 'element2' identifier in the \"bandicoot\" import statement", - "Replaced the 'alias2' identifier with the 'elementAlias2' identifier in the \"bandicoot\" import statement", - "Replaced the \"anaconda\" string with the \"banteng\" string in the \"banteng\" import statement", - "Replaced the 'member1' identifier with the 'element1' identifier in the \"banteng\" import statement", - "Replaced the 'member2' identifier with the 'element2' identifier in the \"banteng\" import statement", - "Replaced the 'alias2' identifier with the 'elementAlias2' identifier in the \"banteng\" import statement", - "Replaced the \"alligator\" string with the \"barbet\" string in the \"barbet\" import statement", - "Replaced the 'name' identifier with the 'element' identifier in the \"barbet\" import statement", - "Replaced the \"arctic-tern\" string with the \"basilisk\" string in the \"basilisk\" import statement" - ] - }, - "errors": {} - }, - "filePaths": [ - "import.js" - ], - "sha1": "e7a974df1ae0a2993d5eeda4edd1b586adffe84f", - "gitDir": "test/corpus/repos/javascript", - "sha2": "ab39b6f04b648cbddfd6afa3470995a0cd6fee69" -} -,{ - "testCaseDescription": "javascript-import-delete-replacement-test", - "expectedResult": { - "changes": { - "import.js": [ - "Deleted the '\"babirusa\"' import statement", - "Deleted the '\"baboon\"' import statement", - "Deleted the '\"badger\"' import statement", - "Deleted the '\"bald-eagle\"' import statement", - "Deleted the '\"bandicoot\"' import statement", - "Deleted the '\"banteng\"' import statement", - "Deleted the '\"barbet\"' import statement", - "Deleted the '\"basilisk\"' import statement", - "Deleted the '\"foo\"' import statement", - "Deleted the '\"aardvark\"' import statement", - "Deleted the '\"ant\"' import statement", - "Deleted the '\"antelope\"' import statement", - "Deleted the '\"ant-eater\"' import statement", - "Deleted the '\"anaconda\"' import statement", - "Deleted the '\"alligator\"' import statement", - "Deleted the '\"arctic-tern\"' import statement", - "Added the '\"babirusa\"' import statement", - "Added the '\"baboon\"' import statement", - "Added the '\"badger\"' import statement", - "Added the '\"bald-eagle\"' import statement", - "Added the '\"bandicoot\"' import statement", - "Added the '\"banteng\"' import statement", - "Added the '\"barbet\"' import statement", - "Added the '\"basilisk\"' import statement" - ] - }, - "errors": {} - }, - "filePaths": [ - "import.js" - ], - "sha1": "ab39b6f04b648cbddfd6afa3470995a0cd6fee69", - "gitDir": "test/corpus/repos/javascript", - "sha2": "e9b593a62e90802adf1e1c7a91e8299116092602" -} -,{ - "testCaseDescription": "javascript-import-delete-test", - "expectedResult": { - "changes": { - "import.js": [ - "Deleted the '\"foo\"' import statement", - "Deleted the '\"aardvark\"' import statement", - "Deleted the '\"ant\"' import statement", - "Deleted the '\"antelope\"' import statement", - "Deleted the '\"ant-eater\"' import statement", - "Deleted the '\"anaconda\"' import statement", - "Deleted the '\"alligator\"' import statement", - "Deleted the '\"arctic-tern\"' import statement" - ] - }, - "errors": {} - }, - "filePaths": [ - "import.js" - ], - "sha1": "e9b593a62e90802adf1e1c7a91e8299116092602", - "gitDir": "test/corpus/repos/javascript", - "sha2": "aca47c2554e1cf1ab3f0864b01040937488a39e5" -} -,{ - "testCaseDescription": "javascript-import-delete-rest-test", - "expectedResult": { - "changes": { - "import.js": [ - "Deleted the '\"babirusa\"' import statement", - "Deleted the '\"baboon\"' import statement", - "Deleted the '\"badger\"' import statement", - "Deleted the '\"bald-eagle\"' import statement", - "Deleted the '\"bandicoot\"' import statement", - "Deleted the '\"banteng\"' import statement", - "Deleted the '\"barbet\"' import statement", - "Deleted the '\"basilisk\"' import statement" - ] - }, - "errors": {} - }, - "filePaths": [ - "import.js" - ], - "sha1": "aca47c2554e1cf1ab3f0864b01040937488a39e5", - "gitDir": "test/corpus/repos/javascript", - "sha2": "fbc5b11fcf02fc81e576ea8ec5d4e590a6a4cf6c" -}] diff --git a/test/corpus/diff-summaries/javascript/math-assignment-operator.json b/test/corpus/diff-summaries/javascript/math-assignment-operator.json deleted file mode 100644 index f66cfec7f..000000000 --- a/test/corpus/diff-summaries/javascript/math-assignment-operator.json +++ /dev/null @@ -1,308 +0,0 @@ -[{ - "testCaseDescription": "javascript-math-assignment-operator-insert-test", - "expectedResult": { - "changes": { - "math-assignment-operator.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "math-assignment-operator.js", - "end": [ - 1, - 7 - ] - } - }, - "summary": "Added the 'x' math assignment", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "math-assignment-operator.js" - ], - "sha1": "74f192419bb6a3a7ef68bb5eb4cf71e89e09b919", - "gitDir": "test/corpus/repos/javascript", - "sha2": "d6da9771070c0da9787ae5e26c8914a45391d67b" -} -,{ - "testCaseDescription": "javascript-math-assignment-operator-replacement-insert-test", - "expectedResult": { - "changes": { - "math-assignment-operator.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "math-assignment-operator.js", - "end": [ - 1, - 7 - ] - } - }, - "summary": "Added the 'x' math assignment", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "math-assignment-operator.js", - "end": [ - 2, - 7 - ] - } - }, - "summary": "Added the 'x' math assignment", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "math-assignment-operator.js" - ], - "sha1": "d6da9771070c0da9787ae5e26c8914a45391d67b", - "gitDir": "test/corpus/repos/javascript", - "sha2": "b817bac77a25047fc74bae958ac96e12e1f0a39e" -} -,{ - "testCaseDescription": "javascript-math-assignment-operator-delete-insert-test", - "expectedResult": { - "changes": { - "math-assignment-operator.js": [ - { - "span": { - "these": [ - { - "start": [ - 1, - 6 - ], - "name": "math-assignment-operator.js", - "end": [ - 1, - 7 - ] - }, - { - "start": [ - 1, - 6 - ], - "name": "math-assignment-operator.js", - "end": [ - 1, - 7 - ] - } - ] - }, - "summary": "Replaced '2' with '1' in the x math assignment", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "math-assignment-operator.js" - ], - "sha1": "b817bac77a25047fc74bae958ac96e12e1f0a39e", - "gitDir": "test/corpus/repos/javascript", - "sha2": "4fe543b5777c4b39ffdeb2a4492405adc704d764" -} -,{ - "testCaseDescription": "javascript-math-assignment-operator-replacement-test", - "expectedResult": { - "changes": { - "math-assignment-operator.js": [ - { - "span": { - "these": [ - { - "start": [ - 1, - 6 - ], - "name": "math-assignment-operator.js", - "end": [ - 1, - 7 - ] - }, - { - "start": [ - 1, - 6 - ], - "name": "math-assignment-operator.js", - "end": [ - 1, - 7 - ] - } - ] - }, - "summary": "Replaced '1' with '2' in the x math assignment", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "math-assignment-operator.js" - ], - "sha1": "4fe543b5777c4b39ffdeb2a4492405adc704d764", - "gitDir": "test/corpus/repos/javascript", - "sha2": "33afe3e3e1c77dabda9ec3e7b99f0c923bc23de5" -} -,{ - "testCaseDescription": "javascript-math-assignment-operator-delete-replacement-test", - "expectedResult": { - "changes": { - "math-assignment-operator.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "math-assignment-operator.js", - "end": [ - 1, - 7 - ] - } - }, - "summary": "Deleted the 'x' math assignment", - "tag": "JSONSummary" - }, - { - "span": { - "this": { - "start": [ - 2, - 1 - ], - "name": "math-assignment-operator.js", - "end": [ - 2, - 7 - ] - } - }, - "summary": "Deleted the 'x' math assignment", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "math-assignment-operator.js", - "end": [ - 2, - 7 - ] - } - }, - "summary": "Added the 'x' math assignment", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "math-assignment-operator.js" - ], - "sha1": "33afe3e3e1c77dabda9ec3e7b99f0c923bc23de5", - "gitDir": "test/corpus/repos/javascript", - "sha2": "3754066fb44624889e799c91af2a609fb1f1d27d" -} -,{ - "testCaseDescription": "javascript-math-assignment-operator-delete-test", - "expectedResult": { - "changes": { - "math-assignment-operator.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "math-assignment-operator.js", - "end": [ - 1, - 7 - ] - } - }, - "summary": "Deleted the 'x' math assignment", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "math-assignment-operator.js" - ], - "sha1": "3754066fb44624889e799c91af2a609fb1f1d27d", - "gitDir": "test/corpus/repos/javascript", - "sha2": "bd1b94d3f2bf9806becf43c7f18927e1ff3932ec" -} -,{ - "testCaseDescription": "javascript-math-assignment-operator-delete-rest-test", - "expectedResult": { - "changes": { - "math-assignment-operator.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "math-assignment-operator.js", - "end": [ - 1, - 7 - ] - } - }, - "summary": "Deleted the 'x' math assignment", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "math-assignment-operator.js" - ], - "sha1": "bd1b94d3f2bf9806becf43c7f18927e1ff3932ec", - "gitDir": "test/corpus/repos/javascript", - "sha2": "faab59d023f70bb2d675e7d0671d36bc82dc9d0f" -}] diff --git a/test/corpus/diff-summaries/javascript/math-operator.json b/test/corpus/diff-summaries/javascript/math-operator.json deleted file mode 100644 index 5ed3ce26a..000000000 --- a/test/corpus/diff-summaries/javascript/math-operator.json +++ /dev/null @@ -1,368 +0,0 @@ -[{ - "testCaseDescription": "javascript-math-operator-insert-test", - "expectedResult": { - "changes": { - "math-operator.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "math-operator.js", - "end": [ - 1, - 18 - ] - } - }, - "summary": "Added the 'i + j * 3 - j % 5' math operator", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "math-operator.js" - ], - "sha1": "a871e92442fa237af75a13a311d49a15bcea9444", - "gitDir": "test/corpus/repos/javascript", - "sha2": "6e6e7267c1e6bc551379dbdf39e3d4ca59d4a60c" -} -,{ - "testCaseDescription": "javascript-math-operator-replacement-insert-test", - "expectedResult": { - "changes": { - "math-operator.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "math-operator.js", - "end": [ - 1, - 18 - ] - } - }, - "summary": "Added the 'i + j * 2 - j % 4' math operator", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "math-operator.js", - "end": [ - 2, - 18 - ] - } - }, - "summary": "Added the 'i + j * 3 - j % 5' math operator", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "math-operator.js" - ], - "sha1": "6e6e7267c1e6bc551379dbdf39e3d4ca59d4a60c", - "gitDir": "test/corpus/repos/javascript", - "sha2": "bf33c9910dcfad10ffafd330c0adff6b7a7f262a" -} -,{ - "testCaseDescription": "javascript-math-operator-delete-insert-test", - "expectedResult": { - "changes": { - "math-operator.js": [ - { - "span": { - "these": [ - { - "start": [ - 1, - 9 - ], - "name": "math-operator.js", - "end": [ - 1, - 10 - ] - }, - { - "start": [ - 1, - 9 - ], - "name": "math-operator.js", - "end": [ - 1, - 10 - ] - } - ] - }, - "summary": "Replaced '2' with '3'", - "tag": "JSONSummary" - }, - { - "span": { - "these": [ - { - "start": [ - 1, - 17 - ], - "name": "math-operator.js", - "end": [ - 1, - 18 - ] - }, - { - "start": [ - 1, - 17 - ], - "name": "math-operator.js", - "end": [ - 1, - 18 - ] - } - ] - }, - "summary": "Replaced '4' with '5'", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "math-operator.js" - ], - "sha1": "bf33c9910dcfad10ffafd330c0adff6b7a7f262a", - "gitDir": "test/corpus/repos/javascript", - "sha2": "bd78c2dd93219f462c6a6823267bd327c14094db" -} -,{ - "testCaseDescription": "javascript-math-operator-replacement-test", - "expectedResult": { - "changes": { - "math-operator.js": [ - { - "span": { - "these": [ - { - "start": [ - 1, - 9 - ], - "name": "math-operator.js", - "end": [ - 1, - 10 - ] - }, - { - "start": [ - 1, - 9 - ], - "name": "math-operator.js", - "end": [ - 1, - 10 - ] - } - ] - }, - "summary": "Replaced '3' with '2'", - "tag": "JSONSummary" - }, - { - "span": { - "these": [ - { - "start": [ - 1, - 17 - ], - "name": "math-operator.js", - "end": [ - 1, - 18 - ] - }, - { - "start": [ - 1, - 17 - ], - "name": "math-operator.js", - "end": [ - 1, - 18 - ] - } - ] - }, - "summary": "Replaced '5' with '4'", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "math-operator.js" - ], - "sha1": "bd78c2dd93219f462c6a6823267bd327c14094db", - "gitDir": "test/corpus/repos/javascript", - "sha2": "413c0d316184bb443b4facd4aec46b4b04f0df71" -} -,{ - "testCaseDescription": "javascript-math-operator-delete-replacement-test", - "expectedResult": { - "changes": { - "math-operator.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "math-operator.js", - "end": [ - 1, - 18 - ] - } - }, - "summary": "Deleted the 'i + j * 2 - j % 4' math operator", - "tag": "JSONSummary" - }, - { - "span": { - "this": { - "start": [ - 2, - 1 - ], - "name": "math-operator.js", - "end": [ - 2, - 18 - ] - } - }, - "summary": "Deleted the 'i + j * 3 - j % 5' math operator", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "math-operator.js", - "end": [ - 2, - 18 - ] - } - }, - "summary": "Added the 'i + j * 2 - j % 4' math operator", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "math-operator.js" - ], - "sha1": "413c0d316184bb443b4facd4aec46b4b04f0df71", - "gitDir": "test/corpus/repos/javascript", - "sha2": "fb9ae3c73391e3158c898052fa343bb7bf98394b" -} -,{ - "testCaseDescription": "javascript-math-operator-delete-test", - "expectedResult": { - "changes": { - "math-operator.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "math-operator.js", - "end": [ - 1, - 18 - ] - } - }, - "summary": "Deleted the 'i + j * 3 - j % 5' math operator", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "math-operator.js" - ], - "sha1": "fb9ae3c73391e3158c898052fa343bb7bf98394b", - "gitDir": "test/corpus/repos/javascript", - "sha2": "9d2684586034ffe1cd50891ac950f9bc2bf40d2e" -} -,{ - "testCaseDescription": "javascript-math-operator-delete-rest-test", - "expectedResult": { - "changes": { - "math-operator.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "math-operator.js", - "end": [ - 1, - 18 - ] - } - }, - "summary": "Deleted the 'i + j * 2 - j % 4' math operator", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "math-operator.js" - ], - "sha1": "9d2684586034ffe1cd50891ac950f9bc2bf40d2e", - "gitDir": "test/corpus/repos/javascript", - "sha2": "d7edfafd0028d88e036ad5af083bd4c0eaf821d5" -}] diff --git a/test/corpus/diff-summaries/javascript/member-access-assignment.json b/test/corpus/diff-summaries/javascript/member-access-assignment.json deleted file mode 100644 index bd9029047..000000000 --- a/test/corpus/diff-summaries/javascript/member-access-assignment.json +++ /dev/null @@ -1,308 +0,0 @@ -[{ - "testCaseDescription": "javascript-member-access-assignment-insert-test", - "expectedResult": { - "changes": { - "member-access-assignment.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "member-access-assignment.js", - "end": [ - 1, - 8 - ] - } - }, - "summary": "Added the 'y.x' assignment", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "member-access-assignment.js" - ], - "sha1": "24ea895fcb8c904a8d057c536eb56be4a8928e33", - "gitDir": "test/corpus/repos/javascript", - "sha2": "2b8bd487139dc144f01faab13961865c633bc0cd" -} -,{ - "testCaseDescription": "javascript-member-access-assignment-replacement-insert-test", - "expectedResult": { - "changes": { - "member-access-assignment.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "member-access-assignment.js", - "end": [ - 1, - 8 - ] - } - }, - "summary": "Added the 'y.x' assignment", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "member-access-assignment.js", - "end": [ - 2, - 8 - ] - } - }, - "summary": "Added the 'y.x' assignment", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "member-access-assignment.js" - ], - "sha1": "2b8bd487139dc144f01faab13961865c633bc0cd", - "gitDir": "test/corpus/repos/javascript", - "sha2": "81f85cdb9f7a17a0560ee3e9d550eb3db0aaa739" -} -,{ - "testCaseDescription": "javascript-member-access-assignment-delete-insert-test", - "expectedResult": { - "changes": { - "member-access-assignment.js": [ - { - "span": { - "these": [ - { - "start": [ - 1, - 7 - ], - "name": "member-access-assignment.js", - "end": [ - 1, - 8 - ] - }, - { - "start": [ - 1, - 7 - ], - "name": "member-access-assignment.js", - "end": [ - 1, - 8 - ] - } - ] - }, - "summary": "Replaced '1' with '0' in an assignment to y.x", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "member-access-assignment.js" - ], - "sha1": "81f85cdb9f7a17a0560ee3e9d550eb3db0aaa739", - "gitDir": "test/corpus/repos/javascript", - "sha2": "30285e2a6c2057ad1af3e8475aa48d75c6e11199" -} -,{ - "testCaseDescription": "javascript-member-access-assignment-replacement-test", - "expectedResult": { - "changes": { - "member-access-assignment.js": [ - { - "span": { - "these": [ - { - "start": [ - 1, - 7 - ], - "name": "member-access-assignment.js", - "end": [ - 1, - 8 - ] - }, - { - "start": [ - 1, - 7 - ], - "name": "member-access-assignment.js", - "end": [ - 1, - 8 - ] - } - ] - }, - "summary": "Replaced '0' with '1' in an assignment to y.x", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "member-access-assignment.js" - ], - "sha1": "30285e2a6c2057ad1af3e8475aa48d75c6e11199", - "gitDir": "test/corpus/repos/javascript", - "sha2": "a2a7e40667563b5b73dcafcbb1e476e9bd2454ba" -} -,{ - "testCaseDescription": "javascript-member-access-assignment-delete-replacement-test", - "expectedResult": { - "changes": { - "member-access-assignment.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "member-access-assignment.js", - "end": [ - 1, - 8 - ] - } - }, - "summary": "Deleted the 'y.x' assignment", - "tag": "JSONSummary" - }, - { - "span": { - "this": { - "start": [ - 2, - 1 - ], - "name": "member-access-assignment.js", - "end": [ - 2, - 8 - ] - } - }, - "summary": "Deleted the 'y.x' assignment", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "member-access-assignment.js", - "end": [ - 2, - 8 - ] - } - }, - "summary": "Added the 'y.x' assignment", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "member-access-assignment.js" - ], - "sha1": "a2a7e40667563b5b73dcafcbb1e476e9bd2454ba", - "gitDir": "test/corpus/repos/javascript", - "sha2": "fd07c5983ef2c5a8857943d86f1df8f7090a4edd" -} -,{ - "testCaseDescription": "javascript-member-access-assignment-delete-test", - "expectedResult": { - "changes": { - "member-access-assignment.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "member-access-assignment.js", - "end": [ - 1, - 8 - ] - } - }, - "summary": "Deleted the 'y.x' assignment", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "member-access-assignment.js" - ], - "sha1": "fd07c5983ef2c5a8857943d86f1df8f7090a4edd", - "gitDir": "test/corpus/repos/javascript", - "sha2": "c9211034900804da82ade93b31c9ea5dfdbfcd35" -} -,{ - "testCaseDescription": "javascript-member-access-assignment-delete-rest-test", - "expectedResult": { - "changes": { - "member-access-assignment.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "member-access-assignment.js", - "end": [ - 1, - 8 - ] - } - }, - "summary": "Deleted the 'y.x' assignment", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "member-access-assignment.js" - ], - "sha1": "c9211034900804da82ade93b31c9ea5dfdbfcd35", - "gitDir": "test/corpus/repos/javascript", - "sha2": "0286a0f0ca80520eb670a372dbf844ec8357639e" -}] diff --git a/test/corpus/diff-summaries/javascript/member-access.json b/test/corpus/diff-summaries/javascript/member-access.json deleted file mode 100644 index b9a2d8e22..000000000 --- a/test/corpus/diff-summaries/javascript/member-access.json +++ /dev/null @@ -1,308 +0,0 @@ -[{ - "testCaseDescription": "javascript-member-access-insert-test", - "expectedResult": { - "changes": { - "member-access.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "member-access.js", - "end": [ - 1, - 15 - ] - } - }, - "summary": "Added the 'x.someProperty' member access", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "member-access.js" - ], - "sha1": "6efc7d3ef6f891602e19a27ed0c598e6c5e179ea", - "gitDir": "test/corpus/repos/javascript", - "sha2": "4c558b5d02c5e2d435f6a4bbfda3da186aa580b0" -} -,{ - "testCaseDescription": "javascript-member-access-replacement-insert-test", - "expectedResult": { - "changes": { - "member-access.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "member-access.js", - "end": [ - 1, - 20 - ] - } - }, - "summary": "Added the 'x.someOtherProperty' member access", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "member-access.js", - "end": [ - 2, - 15 - ] - } - }, - "summary": "Added the 'x.someProperty' member access", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "member-access.js" - ], - "sha1": "4c558b5d02c5e2d435f6a4bbfda3da186aa580b0", - "gitDir": "test/corpus/repos/javascript", - "sha2": "ba2f36530d6780fd4b48247d4e07495ab99ff849" -} -,{ - "testCaseDescription": "javascript-member-access-delete-insert-test", - "expectedResult": { - "changes": { - "member-access.js": [ - { - "span": { - "these": [ - { - "start": [ - 1, - 3 - ], - "name": "member-access.js", - "end": [ - 1, - 20 - ] - }, - { - "start": [ - 1, - 3 - ], - "name": "member-access.js", - "end": [ - 1, - 15 - ] - } - ] - }, - "summary": "Replaced the 'someOtherProperty' identifier with the 'someProperty' identifier", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "member-access.js" - ], - "sha1": "ba2f36530d6780fd4b48247d4e07495ab99ff849", - "gitDir": "test/corpus/repos/javascript", - "sha2": "236df8848d358b1867fec80674da98c30a21fa4f" -} -,{ - "testCaseDescription": "javascript-member-access-replacement-test", - "expectedResult": { - "changes": { - "member-access.js": [ - { - "span": { - "these": [ - { - "start": [ - 1, - 3 - ], - "name": "member-access.js", - "end": [ - 1, - 15 - ] - }, - { - "start": [ - 1, - 3 - ], - "name": "member-access.js", - "end": [ - 1, - 20 - ] - } - ] - }, - "summary": "Replaced the 'someProperty' identifier with the 'someOtherProperty' identifier", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "member-access.js" - ], - "sha1": "236df8848d358b1867fec80674da98c30a21fa4f", - "gitDir": "test/corpus/repos/javascript", - "sha2": "7f5877fc43be3f38c976057116b85bd9e54f4c90" -} -,{ - "testCaseDescription": "javascript-member-access-delete-replacement-test", - "expectedResult": { - "changes": { - "member-access.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "member-access.js", - "end": [ - 1, - 20 - ] - } - }, - "summary": "Deleted the 'x.someOtherProperty' member access", - "tag": "JSONSummary" - }, - { - "span": { - "this": { - "start": [ - 2, - 1 - ], - "name": "member-access.js", - "end": [ - 2, - 15 - ] - } - }, - "summary": "Deleted the 'x.someProperty' member access", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "member-access.js", - "end": [ - 2, - 20 - ] - } - }, - "summary": "Added the 'x.someOtherProperty' member access", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "member-access.js" - ], - "sha1": "7f5877fc43be3f38c976057116b85bd9e54f4c90", - "gitDir": "test/corpus/repos/javascript", - "sha2": "5db12107fe6a175ade7fbff6b24b9d5d32a81ac7" -} -,{ - "testCaseDescription": "javascript-member-access-delete-test", - "expectedResult": { - "changes": { - "member-access.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "member-access.js", - "end": [ - 1, - 15 - ] - } - }, - "summary": "Deleted the 'x.someProperty' member access", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "member-access.js" - ], - "sha1": "5db12107fe6a175ade7fbff6b24b9d5d32a81ac7", - "gitDir": "test/corpus/repos/javascript", - "sha2": "32fa045d3b6ae515ff252d024963fa53f469ecf2" -} -,{ - "testCaseDescription": "javascript-member-access-delete-rest-test", - "expectedResult": { - "changes": { - "member-access.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "member-access.js", - "end": [ - 1, - 20 - ] - } - }, - "summary": "Deleted the 'x.someOtherProperty' member access", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "member-access.js" - ], - "sha1": "32fa045d3b6ae515ff252d024963fa53f469ecf2", - "gitDir": "test/corpus/repos/javascript", - "sha2": "c77d21ce31ff19818614b186e90aa577cc20ce9d" -}] diff --git a/test/corpus/diff-summaries/javascript/method-call.json b/test/corpus/diff-summaries/javascript/method-call.json deleted file mode 100644 index 0d440888f..000000000 --- a/test/corpus/diff-summaries/javascript/method-call.json +++ /dev/null @@ -1,308 +0,0 @@ -[{ - "testCaseDescription": "javascript-method-call-insert-test", - "expectedResult": { - "changes": { - "method-call.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "method-call.js", - "end": [ - 1, - 32 - ] - } - }, - "summary": "Added the 'object.someMethod(arg1, \"arg2\")' method call", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "method-call.js" - ], - "sha1": "1057513972364b1ca48ee19f74fb73ca06119e8c", - "gitDir": "test/corpus/repos/javascript", - "sha2": "e331bc52539866046826efc023575d5fd3db6165" -} -,{ - "testCaseDescription": "javascript-method-call-replacement-insert-test", - "expectedResult": { - "changes": { - "method-call.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "method-call.js", - "end": [ - 1, - 32 - ] - } - }, - "summary": "Added the 'object.someMethod(arg1, \"arg3\")' method call", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "method-call.js", - "end": [ - 2, - 32 - ] - } - }, - "summary": "Added the 'object.someMethod(arg1, \"arg2\")' method call", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "method-call.js" - ], - "sha1": "e331bc52539866046826efc023575d5fd3db6165", - "gitDir": "test/corpus/repos/javascript", - "sha2": "bd24f5dadbf7a65bd231a338e6159df321dd57f5" -} -,{ - "testCaseDescription": "javascript-method-call-delete-insert-test", - "expectedResult": { - "changes": { - "method-call.js": [ - { - "span": { - "these": [ - { - "start": [ - 1, - 25 - ], - "name": "method-call.js", - "end": [ - 1, - 31 - ] - }, - { - "start": [ - 1, - 25 - ], - "name": "method-call.js", - "end": [ - 1, - 31 - ] - } - ] - }, - "summary": "Replaced the \"arg3\" string with the \"arg2\" string in the object.someMethod(arg1, \"arg2\") method call", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "method-call.js" - ], - "sha1": "bd24f5dadbf7a65bd231a338e6159df321dd57f5", - "gitDir": "test/corpus/repos/javascript", - "sha2": "13271135545e9d65b6ff2a4c7c28616aad1184e6" -} -,{ - "testCaseDescription": "javascript-method-call-replacement-test", - "expectedResult": { - "changes": { - "method-call.js": [ - { - "span": { - "these": [ - { - "start": [ - 1, - 25 - ], - "name": "method-call.js", - "end": [ - 1, - 31 - ] - }, - { - "start": [ - 1, - 25 - ], - "name": "method-call.js", - "end": [ - 1, - 31 - ] - } - ] - }, - "summary": "Replaced the \"arg2\" string with the \"arg3\" string in the object.someMethod(arg1, \"arg3\") method call", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "method-call.js" - ], - "sha1": "13271135545e9d65b6ff2a4c7c28616aad1184e6", - "gitDir": "test/corpus/repos/javascript", - "sha2": "1c29343f384ab78feb8d55b28d06ca5b2c2a1543" -} -,{ - "testCaseDescription": "javascript-method-call-delete-replacement-test", - "expectedResult": { - "changes": { - "method-call.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "method-call.js", - "end": [ - 1, - 32 - ] - } - }, - "summary": "Deleted the 'object.someMethod(arg1, \"arg3\")' method call", - "tag": "JSONSummary" - }, - { - "span": { - "this": { - "start": [ - 2, - 1 - ], - "name": "method-call.js", - "end": [ - 2, - 32 - ] - } - }, - "summary": "Deleted the 'object.someMethod(arg1, \"arg2\")' method call", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "method-call.js", - "end": [ - 2, - 32 - ] - } - }, - "summary": "Added the 'object.someMethod(arg1, \"arg3\")' method call", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "method-call.js" - ], - "sha1": "1c29343f384ab78feb8d55b28d06ca5b2c2a1543", - "gitDir": "test/corpus/repos/javascript", - "sha2": "f61923d7461a07df3744705230e56b12f0b2d216" -} -,{ - "testCaseDescription": "javascript-method-call-delete-test", - "expectedResult": { - "changes": { - "method-call.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "method-call.js", - "end": [ - 1, - 32 - ] - } - }, - "summary": "Deleted the 'object.someMethod(arg1, \"arg2\")' method call", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "method-call.js" - ], - "sha1": "f61923d7461a07df3744705230e56b12f0b2d216", - "gitDir": "test/corpus/repos/javascript", - "sha2": "5f7fc9da90b24df9a9ad1ff1eae1b3a00657f16e" -} -,{ - "testCaseDescription": "javascript-method-call-delete-rest-test", - "expectedResult": { - "changes": { - "method-call.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "method-call.js", - "end": [ - 1, - 32 - ] - } - }, - "summary": "Deleted the 'object.someMethod(arg1, \"arg3\")' method call", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "method-call.js" - ], - "sha1": "5f7fc9da90b24df9a9ad1ff1eae1b3a00657f16e", - "gitDir": "test/corpus/repos/javascript", - "sha2": "101b21dd5ae54a69443d6899a30f575b0500e085" -}] diff --git a/test/corpus/diff-summaries/javascript/named-function.json b/test/corpus/diff-summaries/javascript/named-function.json deleted file mode 100644 index 447fd80fc..000000000 --- a/test/corpus/diff-summaries/javascript/named-function.json +++ /dev/null @@ -1,444 +0,0 @@ -[{ - "testCaseDescription": "javascript-named-function-insert-test", - "expectedResult": { - "changes": { - "named-function.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "named-function.js", - "end": [ - 1, - 42 - ] - } - }, - "summary": "Added the 'myFunction' function", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "named-function.js" - ], - "sha1": "2f00ecb14d10a4cc210b7a56309fc75db90f3b64", - "gitDir": "test/corpus/repos/javascript", - "sha2": "e87e0464ade6d9ccfcf8858e8360eed0892ac9d2" -} -,{ - "testCaseDescription": "javascript-named-function-replacement-insert-test", - "expectedResult": { - "changes": { - "named-function.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "named-function.js", - "end": [ - 1, - 45 - ] - } - }, - "summary": "Added the 'anotherFunction' function", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "named-function.js", - "end": [ - 2, - 42 - ] - } - }, - "summary": "Added the 'myFunction' function", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "named-function.js" - ], - "sha1": "e87e0464ade6d9ccfcf8858e8360eed0892ac9d2", - "gitDir": "test/corpus/repos/javascript", - "sha2": "233d845790d1fb1c6914aa56ee916044c1491955" -} -,{ - "testCaseDescription": "javascript-named-function-delete-insert-test", - "expectedResult": { - "changes": { - "named-function.js": [ - { - "span": { - "these": [ - { - "start": [ - 1, - 10 - ], - "name": "named-function.js", - "end": [ - 1, - 25 - ] - }, - { - "start": [ - 1, - 10 - ], - "name": "named-function.js", - "end": [ - 1, - 20 - ] - } - ] - }, - "summary": "Replaced the 'anotherFunction' identifier with the 'myFunction' identifier in the myFunction function", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 1, - 21 - ], - "name": "named-function.js", - "end": [ - 1, - 25 - ] - } - }, - "summary": "Added the 'arg1' identifier in the myFunction function", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 1, - 27 - ], - "name": "named-function.js", - "end": [ - 1, - 31 - ] - } - }, - "summary": "Added the 'arg2' identifier in the myFunction function", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 1, - 35 - ], - "name": "named-function.js", - "end": [ - 1, - 39 - ] - } - }, - "summary": "Added the 'arg2' identifier in the myFunction function", - "tag": "JSONSummary" - }, - { - "span": { - "this": { - "start": [ - 1, - 30 - ], - "name": "named-function.js", - "end": [ - 1, - 43 - ] - } - }, - "summary": "Deleted the 'false' return statement in the myFunction function", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "named-function.js" - ], - "sha1": "233d845790d1fb1c6914aa56ee916044c1491955", - "gitDir": "test/corpus/repos/javascript", - "sha2": "6591af1b718467293fb40094d31d8bcd1bc0a679" -} -,{ - "testCaseDescription": "javascript-named-function-replacement-test", - "expectedResult": { - "changes": { - "named-function.js": [ - { - "span": { - "these": [ - { - "start": [ - 1, - 10 - ], - "name": "named-function.js", - "end": [ - 1, - 20 - ] - }, - { - "start": [ - 1, - 10 - ], - "name": "named-function.js", - "end": [ - 1, - 25 - ] - } - ] - }, - "summary": "Replaced the 'myFunction' identifier with the 'anotherFunction' identifier in the anotherFunction function", - "tag": "JSONSummary" - }, - { - "span": { - "this": { - "start": [ - 1, - 21 - ], - "name": "named-function.js", - "end": [ - 1, - 25 - ] - } - }, - "summary": "Deleted the 'arg1' identifier in the anotherFunction function", - "tag": "JSONSummary" - }, - { - "span": { - "this": { - "start": [ - 1, - 27 - ], - "name": "named-function.js", - "end": [ - 1, - 31 - ] - } - }, - "summary": "Deleted the 'arg2' identifier in the anotherFunction function", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 1, - 30 - ], - "name": "named-function.js", - "end": [ - 1, - 43 - ] - } - }, - "summary": "Added the 'false' return statement in the anotherFunction function", - "tag": "JSONSummary" - }, - { - "span": { - "this": { - "start": [ - 1, - 35 - ], - "name": "named-function.js", - "end": [ - 1, - 39 - ] - } - }, - "summary": "Deleted the 'arg2' identifier in the anotherFunction function", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "named-function.js" - ], - "sha1": "6591af1b718467293fb40094d31d8bcd1bc0a679", - "gitDir": "test/corpus/repos/javascript", - "sha2": "ea7b2d944b9f4b906b750883dc50754096ac197d" -} -,{ - "testCaseDescription": "javascript-named-function-delete-replacement-test", - "expectedResult": { - "changes": { - "named-function.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "named-function.js", - "end": [ - 1, - 45 - ] - } - }, - "summary": "Deleted the 'anotherFunction' function", - "tag": "JSONSummary" - }, - { - "span": { - "this": { - "start": [ - 2, - 1 - ], - "name": "named-function.js", - "end": [ - 2, - 42 - ] - } - }, - "summary": "Deleted the 'myFunction' function", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "named-function.js", - "end": [ - 2, - 45 - ] - } - }, - "summary": "Added the 'anotherFunction' function", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "named-function.js" - ], - "sha1": "ea7b2d944b9f4b906b750883dc50754096ac197d", - "gitDir": "test/corpus/repos/javascript", - "sha2": "d5d86035b6457b7e1f55cbe249d2f36cca54ca86" -} -,{ - "testCaseDescription": "javascript-named-function-delete-test", - "expectedResult": { - "changes": { - "named-function.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "named-function.js", - "end": [ - 1, - 42 - ] - } - }, - "summary": "Deleted the 'myFunction' function", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "named-function.js" - ], - "sha1": "d5d86035b6457b7e1f55cbe249d2f36cca54ca86", - "gitDir": "test/corpus/repos/javascript", - "sha2": "ac73db0211c8b73c9ce79a3c730606fdfca84dbe" -} -,{ - "testCaseDescription": "javascript-named-function-delete-rest-test", - "expectedResult": { - "changes": { - "named-function.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "named-function.js", - "end": [ - 1, - 45 - ] - } - }, - "summary": "Deleted the 'anotherFunction' function", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "named-function.js" - ], - "sha1": "ac73db0211c8b73c9ce79a3c730606fdfca84dbe", - "gitDir": "test/corpus/repos/javascript", - "sha2": "6efc7d3ef6f891602e19a27ed0c598e6c5e179ea" -}] diff --git a/test/corpus/diff-summaries/javascript/nested-do-while-in-function.json b/test/corpus/diff-summaries/javascript/nested-do-while-in-function.json deleted file mode 100644 index 6f459bbf9..000000000 --- a/test/corpus/diff-summaries/javascript/nested-do-while-in-function.json +++ /dev/null @@ -1,368 +0,0 @@ -[{ - "testCaseDescription": "javascript-nested-do-while-in-function-insert-test", - "expectedResult": { - "changes": { - "nested-do-while-in-function.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "nested-do-while-in-function.js", - "end": [ - 1, - 65 - ] - } - }, - "summary": "Added the 'f' function", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "nested-do-while-in-function.js" - ], - "sha1": "70ec1b887cd3227d1db143720c9f83c6aee76857", - "gitDir": "test/corpus/repos/javascript", - "sha2": "40718757d69121812c5a1b88b6b254d91fff927d" -} -,{ - "testCaseDescription": "javascript-nested-do-while-in-function-replacement-insert-test", - "expectedResult": { - "changes": { - "nested-do-while-in-function.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "nested-do-while-in-function.js", - "end": [ - 1, - 65 - ] - } - }, - "summary": "Added the 'f' function", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "nested-do-while-in-function.js", - "end": [ - 2, - 65 - ] - } - }, - "summary": "Added the 'f' function", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "nested-do-while-in-function.js" - ], - "sha1": "40718757d69121812c5a1b88b6b254d91fff927d", - "gitDir": "test/corpus/repos/javascript", - "sha2": "f62ea5ca3fd0fa46620b5e5794eb8e70b1699e51" -} -,{ - "testCaseDescription": "javascript-nested-do-while-in-function-delete-insert-test", - "expectedResult": { - "changes": { - "nested-do-while-in-function.js": [ - { - "span": { - "these": [ - { - "start": [ - 1, - 41 - ], - "name": "nested-do-while-in-function.js", - "end": [ - 1, - 45 - ] - }, - { - "start": [ - 1, - 41 - ], - "name": "nested-do-while-in-function.js", - "end": [ - 1, - 45 - ] - } - ] - }, - "summary": "Replaced the 'arg2' identifier with the 'arg1' identifier in the something(arg1) function call of the 'f' function", - "tag": "JSONSummary" - }, - { - "span": { - "these": [ - { - "start": [ - 1, - 57 - ], - "name": "nested-do-while-in-function.js", - "end": [ - 1, - 61 - ] - }, - { - "start": [ - 1, - 57 - ], - "name": "nested-do-while-in-function.js", - "end": [ - 1, - 61 - ] - } - ] - }, - "summary": "Replaced the 'arg1' identifier with the 'arg2' identifier in the arg2 do/while statement of the 'f' function", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "nested-do-while-in-function.js" - ], - "sha1": "f62ea5ca3fd0fa46620b5e5794eb8e70b1699e51", - "gitDir": "test/corpus/repos/javascript", - "sha2": "c89b566e205a722065b4898e103cb48518469ae4" -} -,{ - "testCaseDescription": "javascript-nested-do-while-in-function-replacement-test", - "expectedResult": { - "changes": { - "nested-do-while-in-function.js": [ - { - "span": { - "these": [ - { - "start": [ - 1, - 41 - ], - "name": "nested-do-while-in-function.js", - "end": [ - 1, - 45 - ] - }, - { - "start": [ - 1, - 41 - ], - "name": "nested-do-while-in-function.js", - "end": [ - 1, - 45 - ] - } - ] - }, - "summary": "Replaced the 'arg1' identifier with the 'arg2' identifier in the something(arg2) function call of the 'f' function", - "tag": "JSONSummary" - }, - { - "span": { - "these": [ - { - "start": [ - 1, - 57 - ], - "name": "nested-do-while-in-function.js", - "end": [ - 1, - 61 - ] - }, - { - "start": [ - 1, - 57 - ], - "name": "nested-do-while-in-function.js", - "end": [ - 1, - 61 - ] - } - ] - }, - "summary": "Replaced the 'arg2' identifier with the 'arg1' identifier in the arg1 do/while statement of the 'f' function", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "nested-do-while-in-function.js" - ], - "sha1": "c89b566e205a722065b4898e103cb48518469ae4", - "gitDir": "test/corpus/repos/javascript", - "sha2": "f56c46085db0b8db31cfa4540af347117d489e8b" -} -,{ - "testCaseDescription": "javascript-nested-do-while-in-function-delete-replacement-test", - "expectedResult": { - "changes": { - "nested-do-while-in-function.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "nested-do-while-in-function.js", - "end": [ - 1, - 65 - ] - } - }, - "summary": "Deleted the 'f' function", - "tag": "JSONSummary" - }, - { - "span": { - "this": { - "start": [ - 2, - 1 - ], - "name": "nested-do-while-in-function.js", - "end": [ - 2, - 65 - ] - } - }, - "summary": "Deleted the 'f' function", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "nested-do-while-in-function.js", - "end": [ - 2, - 65 - ] - } - }, - "summary": "Added the 'f' function", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "nested-do-while-in-function.js" - ], - "sha1": "f56c46085db0b8db31cfa4540af347117d489e8b", - "gitDir": "test/corpus/repos/javascript", - "sha2": "c3a81eba697a0b359b9a762fed814b36cafd9f0f" -} -,{ - "testCaseDescription": "javascript-nested-do-while-in-function-delete-test", - "expectedResult": { - "changes": { - "nested-do-while-in-function.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "nested-do-while-in-function.js", - "end": [ - 1, - 65 - ] - } - }, - "summary": "Deleted the 'f' function", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "nested-do-while-in-function.js" - ], - "sha1": "c3a81eba697a0b359b9a762fed814b36cafd9f0f", - "gitDir": "test/corpus/repos/javascript", - "sha2": "4278eca970eb128b7ea79e9b227763b4726f3acd" -} -,{ - "testCaseDescription": "javascript-nested-do-while-in-function-delete-rest-test", - "expectedResult": { - "changes": { - "nested-do-while-in-function.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "nested-do-while-in-function.js", - "end": [ - 1, - 65 - ] - } - }, - "summary": "Deleted the 'f' function", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "nested-do-while-in-function.js" - ], - "sha1": "4278eca970eb128b7ea79e9b227763b4726f3acd", - "gitDir": "test/corpus/repos/javascript", - "sha2": "14310ea870b177f2187e152498699c8cd1b039f3" -}] diff --git a/test/corpus/diff-summaries/javascript/nested-functions.json b/test/corpus/diff-summaries/javascript/nested-functions.json deleted file mode 100644 index 643c18f23..000000000 --- a/test/corpus/diff-summaries/javascript/nested-functions.json +++ /dev/null @@ -1,368 +0,0 @@ -[{ - "testCaseDescription": "javascript-nested-functions-insert-test", - "expectedResult": { - "changes": { - "nested-functions.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "nested-functions.js", - "end": [ - 1, - 103 - ] - } - }, - "summary": "Added the 'parent' function", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "nested-functions.js" - ], - "sha1": "2747446a2e77138d8a05f4ac9068b6c2fefe8c3d", - "gitDir": "test/corpus/repos/javascript", - "sha2": "dc05fc47073a90674b27dd52f2e20157d4bbb692" -} -,{ - "testCaseDescription": "javascript-nested-functions-replacement-insert-test", - "expectedResult": { - "changes": { - "nested-functions.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "nested-functions.js", - "end": [ - 1, - 103 - ] - } - }, - "summary": "Added the 'parent' function", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "nested-functions.js", - "end": [ - 2, - 103 - ] - } - }, - "summary": "Added the 'parent' function", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "nested-functions.js" - ], - "sha1": "dc05fc47073a90674b27dd52f2e20157d4bbb692", - "gitDir": "test/corpus/repos/javascript", - "sha2": "ceda9837fa4d5f417bc943f0df77c878b51e4620" -} -,{ - "testCaseDescription": "javascript-nested-functions-delete-insert-test", - "expectedResult": { - "changes": { - "nested-functions.js": [ - { - "span": { - "these": [ - { - "start": [ - 1, - 74 - ], - "name": "nested-functions.js", - "end": [ - 1, - 78 - ] - }, - { - "start": [ - 1, - 74 - ], - "name": "nested-functions.js", - "end": [ - 1, - 78 - ] - } - ] - }, - "summary": "Replaced the 'arg1' identifier with the 'arg3' identifier in the console.log(arg3) method call of the 'child' function", - "tag": "JSONSummary" - }, - { - "span": { - "these": [ - { - "start": [ - 1, - 93 - ], - "name": "nested-functions.js", - "end": [ - 1, - 97 - ] - }, - { - "start": [ - 1, - 93 - ], - "name": "nested-functions.js", - "end": [ - 1, - 97 - ] - } - ] - }, - "summary": "Replaced the 'arg2' identifier with the 'arg4' identifier in the console.log(arg4) method call of the 'child' function", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "nested-functions.js" - ], - "sha1": "ceda9837fa4d5f417bc943f0df77c878b51e4620", - "gitDir": "test/corpus/repos/javascript", - "sha2": "31c2d106f210aa5efc7ffc2d638d12ad48229812" -} -,{ - "testCaseDescription": "javascript-nested-functions-replacement-test", - "expectedResult": { - "changes": { - "nested-functions.js": [ - { - "span": { - "these": [ - { - "start": [ - 1, - 74 - ], - "name": "nested-functions.js", - "end": [ - 1, - 78 - ] - }, - { - "start": [ - 1, - 74 - ], - "name": "nested-functions.js", - "end": [ - 1, - 78 - ] - } - ] - }, - "summary": "Replaced the 'arg3' identifier with the 'arg1' identifier in the console.log(arg1) method call of the 'child' function", - "tag": "JSONSummary" - }, - { - "span": { - "these": [ - { - "start": [ - 1, - 93 - ], - "name": "nested-functions.js", - "end": [ - 1, - 97 - ] - }, - { - "start": [ - 1, - 93 - ], - "name": "nested-functions.js", - "end": [ - 1, - 97 - ] - } - ] - }, - "summary": "Replaced the 'arg4' identifier with the 'arg2' identifier in the console.log(arg2) method call of the 'child' function", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "nested-functions.js" - ], - "sha1": "31c2d106f210aa5efc7ffc2d638d12ad48229812", - "gitDir": "test/corpus/repos/javascript", - "sha2": "98eb2195462290eb69d5a2a744c9d1979899bbe8" -} -,{ - "testCaseDescription": "javascript-nested-functions-delete-replacement-test", - "expectedResult": { - "changes": { - "nested-functions.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "nested-functions.js", - "end": [ - 1, - 103 - ] - } - }, - "summary": "Deleted the 'parent' function", - "tag": "JSONSummary" - }, - { - "span": { - "this": { - "start": [ - 2, - 1 - ], - "name": "nested-functions.js", - "end": [ - 2, - 103 - ] - } - }, - "summary": "Deleted the 'parent' function", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "nested-functions.js", - "end": [ - 2, - 103 - ] - } - }, - "summary": "Added the 'parent' function", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "nested-functions.js" - ], - "sha1": "98eb2195462290eb69d5a2a744c9d1979899bbe8", - "gitDir": "test/corpus/repos/javascript", - "sha2": "f6573d0d559b96309ebf0d5079e43976d0bc7fe8" -} -,{ - "testCaseDescription": "javascript-nested-functions-delete-test", - "expectedResult": { - "changes": { - "nested-functions.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "nested-functions.js", - "end": [ - 1, - 103 - ] - } - }, - "summary": "Deleted the 'parent' function", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "nested-functions.js" - ], - "sha1": "f6573d0d559b96309ebf0d5079e43976d0bc7fe8", - "gitDir": "test/corpus/repos/javascript", - "sha2": "23cf31d25f6690285855642d7471b14c8c0679b0" -} -,{ - "testCaseDescription": "javascript-nested-functions-delete-rest-test", - "expectedResult": { - "changes": { - "nested-functions.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "nested-functions.js", - "end": [ - 1, - 103 - ] - } - }, - "summary": "Deleted the 'parent' function", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "nested-functions.js" - ], - "sha1": "23cf31d25f6690285855642d7471b14c8c0679b0", - "gitDir": "test/corpus/repos/javascript", - "sha2": "70ec1b887cd3227d1db143720c9f83c6aee76857" -}] diff --git a/test/corpus/diff-summaries/javascript/null.json b/test/corpus/diff-summaries/javascript/null.json deleted file mode 100644 index 487cef6ee..000000000 --- a/test/corpus/diff-summaries/javascript/null.json +++ /dev/null @@ -1,316 +0,0 @@ -[{ - "testCaseDescription": "javascript-null-insert-test", - "expectedResult": { - "changes": { - "null.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "null.js", - "end": [ - 1, - 5 - ] - } - }, - "summary": "Added the 'null' identifier", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "null.js" - ], - "sha1": "11a27a81f8e7e33aac2eb0844d3465acf8f9bb0d", - "gitDir": "test/corpus/repos/javascript", - "sha2": "eb6644a70a4cd3a9d3cc65812e3ac5c1a4d76520" -} -,{ - "testCaseDescription": "javascript-null-replacement-insert-test", - "expectedResult": { - "changes": { - "null.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "null.js", - "end": [ - 1, - 13 - ] - } - }, - "summary": "Added the 'null' return statement", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "null.js", - "end": [ - 2, - 5 - ] - } - }, - "summary": "Added the 'null' identifier", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "null.js" - ], - "sha1": "eb6644a70a4cd3a9d3cc65812e3ac5c1a4d76520", - "gitDir": "test/corpus/repos/javascript", - "sha2": "94a5c1d61909967783e1c9acca96fdf47cde7f3e" -} -,{ - "testCaseDescription": "javascript-null-delete-insert-test", - "expectedResult": { - "changes": { - "null.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "null.js", - "end": [ - 1, - 5 - ] - } - }, - "summary": "Added the 'null' identifier", - "tag": "JSONSummary" - }, - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "null.js", - "end": [ - 1, - 13 - ] - } - }, - "summary": "Deleted the 'null' return statement", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "null.js" - ], - "sha1": "94a5c1d61909967783e1c9acca96fdf47cde7f3e", - "gitDir": "test/corpus/repos/javascript", - "sha2": "5dcff49942934eff57dac635ed367b34a9579c9c" -} -,{ - "testCaseDescription": "javascript-null-replacement-test", - "expectedResult": { - "changes": { - "null.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "null.js", - "end": [ - 1, - 13 - ] - } - }, - "summary": "Added the 'null' return statement", - "tag": "JSONSummary" - }, - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "null.js", - "end": [ - 1, - 5 - ] - } - }, - "summary": "Deleted the 'null' identifier", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "null.js" - ], - "sha1": "5dcff49942934eff57dac635ed367b34a9579c9c", - "gitDir": "test/corpus/repos/javascript", - "sha2": "606f0007b3d2e0c89cce1fbc92d0fbbeaff87c11" -} -,{ - "testCaseDescription": "javascript-null-delete-replacement-test", - "expectedResult": { - "changes": { - "null.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "null.js", - "end": [ - 1, - 13 - ] - } - }, - "summary": "Deleted the 'null' return statement", - "tag": "JSONSummary" - }, - { - "span": { - "this": { - "start": [ - 2, - 1 - ], - "name": "null.js", - "end": [ - 2, - 5 - ] - } - }, - "summary": "Deleted the 'null' identifier", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "null.js", - "end": [ - 2, - 13 - ] - } - }, - "summary": "Added the 'null' return statement", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "null.js" - ], - "sha1": "606f0007b3d2e0c89cce1fbc92d0fbbeaff87c11", - "gitDir": "test/corpus/repos/javascript", - "sha2": "1142c2c15d6730bb2bfa0be5f76115ca4667064c" -} -,{ - "testCaseDescription": "javascript-null-delete-test", - "expectedResult": { - "changes": { - "null.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "null.js", - "end": [ - 1, - 5 - ] - } - }, - "summary": "Deleted the 'null' identifier", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "null.js" - ], - "sha1": "1142c2c15d6730bb2bfa0be5f76115ca4667064c", - "gitDir": "test/corpus/repos/javascript", - "sha2": "74f6868171e2ab7e8a4e77d6b07d1e7c1dcb6b07" -} -,{ - "testCaseDescription": "javascript-null-delete-rest-test", - "expectedResult": { - "changes": { - "null.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "null.js", - "end": [ - 1, - 13 - ] - } - }, - "summary": "Deleted the 'null' return statement", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "null.js" - ], - "sha1": "74f6868171e2ab7e8a4e77d6b07d1e7c1dcb6b07", - "gitDir": "test/corpus/repos/javascript", - "sha2": "43fd131de0f55fa1826e3fa3b95b88b7ba74fd68" -}] diff --git a/test/corpus/diff-summaries/javascript/number.json b/test/corpus/diff-summaries/javascript/number.json deleted file mode 100644 index 9699bd31a..000000000 --- a/test/corpus/diff-summaries/javascript/number.json +++ /dev/null @@ -1,308 +0,0 @@ -[{ - "testCaseDescription": "javascript-number-insert-test", - "expectedResult": { - "changes": { - "number.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "number.js", - "end": [ - 1, - 4 - ] - } - }, - "summary": "Added '101'", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "number.js" - ], - "sha1": "6353fa1218bad4624b606cf46bfcd6c18d1e13c2", - "gitDir": "test/corpus/repos/javascript", - "sha2": "7c7876c3c6be4f9f70b5b83ea763df7301fcd684" -} -,{ - "testCaseDescription": "javascript-number-replacement-insert-test", - "expectedResult": { - "changes": { - "number.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "number.js", - "end": [ - 1, - 4 - ] - } - }, - "summary": "Added '102'", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "number.js", - "end": [ - 2, - 4 - ] - } - }, - "summary": "Added '101'", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "number.js" - ], - "sha1": "7c7876c3c6be4f9f70b5b83ea763df7301fcd684", - "gitDir": "test/corpus/repos/javascript", - "sha2": "504616415391cd15d571dad61cf0df37572cc9a9" -} -,{ - "testCaseDescription": "javascript-number-delete-insert-test", - "expectedResult": { - "changes": { - "number.js": [ - { - "span": { - "these": [ - { - "start": [ - 1, - 1 - ], - "name": "number.js", - "end": [ - 1, - 4 - ] - }, - { - "start": [ - 1, - 1 - ], - "name": "number.js", - "end": [ - 1, - 4 - ] - } - ] - }, - "summary": "Replaced '102' with '101'", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "number.js" - ], - "sha1": "504616415391cd15d571dad61cf0df37572cc9a9", - "gitDir": "test/corpus/repos/javascript", - "sha2": "63450eae5510a793bdf738ccd7956bce348ce393" -} -,{ - "testCaseDescription": "javascript-number-replacement-test", - "expectedResult": { - "changes": { - "number.js": [ - { - "span": { - "these": [ - { - "start": [ - 1, - 1 - ], - "name": "number.js", - "end": [ - 1, - 4 - ] - }, - { - "start": [ - 1, - 1 - ], - "name": "number.js", - "end": [ - 1, - 4 - ] - } - ] - }, - "summary": "Replaced '101' with '102'", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "number.js" - ], - "sha1": "63450eae5510a793bdf738ccd7956bce348ce393", - "gitDir": "test/corpus/repos/javascript", - "sha2": "db793bae2da69d2c4d00dd90611a9cd5913a5efc" -} -,{ - "testCaseDescription": "javascript-number-delete-replacement-test", - "expectedResult": { - "changes": { - "number.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "number.js", - "end": [ - 1, - 4 - ] - } - }, - "summary": "Deleted '102'", - "tag": "JSONSummary" - }, - { - "span": { - "this": { - "start": [ - 2, - 1 - ], - "name": "number.js", - "end": [ - 2, - 4 - ] - } - }, - "summary": "Deleted '101'", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "number.js", - "end": [ - 2, - 4 - ] - } - }, - "summary": "Added '102'", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "number.js" - ], - "sha1": "db793bae2da69d2c4d00dd90611a9cd5913a5efc", - "gitDir": "test/corpus/repos/javascript", - "sha2": "0c5dcd56a648d9cf91377e14604afa2f64ca6738" -} -,{ - "testCaseDescription": "javascript-number-delete-test", - "expectedResult": { - "changes": { - "number.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "number.js", - "end": [ - 1, - 4 - ] - } - }, - "summary": "Deleted '101'", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "number.js" - ], - "sha1": "0c5dcd56a648d9cf91377e14604afa2f64ca6738", - "gitDir": "test/corpus/repos/javascript", - "sha2": "ccdba59644ee3190b25f1975f8ef24c0d0a39a1c" -} -,{ - "testCaseDescription": "javascript-number-delete-rest-test", - "expectedResult": { - "changes": { - "number.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "number.js", - "end": [ - 1, - 4 - ] - } - }, - "summary": "Deleted '102'", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "number.js" - ], - "sha1": "ccdba59644ee3190b25f1975f8ef24c0d0a39a1c", - "gitDir": "test/corpus/repos/javascript", - "sha2": "7cd0762fb1e84cad3dcf9a1c41b07c8112c888fd" -}] diff --git a/test/corpus/diff-summaries/javascript/object-with-methods.json b/test/corpus/diff-summaries/javascript/object-with-methods.json deleted file mode 100644 index 75daf0972..000000000 --- a/test/corpus/diff-summaries/javascript/object-with-methods.json +++ /dev/null @@ -1,308 +0,0 @@ -[{ - "testCaseDescription": "javascript-objects-with-methods-insert-test", - "expectedResult": { - "changes": { - "objects-with-methods.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "objects-with-methods.js", - "end": [ - 1, - 32 - ] - } - }, - "summary": "Added the '{ add }' object", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "objects-with-methods.js" - ], - "sha1": "59872fcdcee9cd22104933bbc925d9987cd393b6", - "gitDir": "test/corpus/repos/javascript", - "sha2": "b3aa3244e4a63ad27cee5f101e357a16bbb6e3b5" -} -,{ - "testCaseDescription": "javascript-objects-with-methods-replacement-insert-test", - "expectedResult": { - "changes": { - "objects-with-methods.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "objects-with-methods.js", - "end": [ - 1, - 37 - ] - } - }, - "summary": "Added the '{ subtract }' object", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "objects-with-methods.js", - "end": [ - 2, - 32 - ] - } - }, - "summary": "Added the '{ add }' object", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "objects-with-methods.js" - ], - "sha1": "b3aa3244e4a63ad27cee5f101e357a16bbb6e3b5", - "gitDir": "test/corpus/repos/javascript", - "sha2": "8dbd1ca6c20e067e9a66b00e6e9eb883d0ee3635" -} -,{ - "testCaseDescription": "javascript-objects-with-methods-delete-insert-test", - "expectedResult": { - "changes": { - "objects-with-methods.js": [ - { - "span": { - "these": [ - { - "start": [ - 1, - 3 - ], - "name": "objects-with-methods.js", - "end": [ - 1, - 11 - ] - }, - { - "start": [ - 1, - 3 - ], - "name": "objects-with-methods.js", - "end": [ - 1, - 6 - ] - } - ] - }, - "summary": "Replaced the 'subtract' identifier with the 'add' identifier in the add method", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "objects-with-methods.js" - ], - "sha1": "8dbd1ca6c20e067e9a66b00e6e9eb883d0ee3635", - "gitDir": "test/corpus/repos/javascript", - "sha2": "e14f2325776fdfc3c455b97c477dda641cf9fa04" -} -,{ - "testCaseDescription": "javascript-objects-with-methods-replacement-test", - "expectedResult": { - "changes": { - "objects-with-methods.js": [ - { - "span": { - "these": [ - { - "start": [ - 1, - 3 - ], - "name": "objects-with-methods.js", - "end": [ - 1, - 6 - ] - }, - { - "start": [ - 1, - 3 - ], - "name": "objects-with-methods.js", - "end": [ - 1, - 11 - ] - } - ] - }, - "summary": "Replaced the 'add' identifier with the 'subtract' identifier in the subtract method", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "objects-with-methods.js" - ], - "sha1": "e14f2325776fdfc3c455b97c477dda641cf9fa04", - "gitDir": "test/corpus/repos/javascript", - "sha2": "7b8889fcf97d4f9b27d986f7dbedea7ab1b737d0" -} -,{ - "testCaseDescription": "javascript-objects-with-methods-delete-replacement-test", - "expectedResult": { - "changes": { - "objects-with-methods.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "objects-with-methods.js", - "end": [ - 1, - 37 - ] - } - }, - "summary": "Deleted the '{ subtract }' object", - "tag": "JSONSummary" - }, - { - "span": { - "this": { - "start": [ - 2, - 1 - ], - "name": "objects-with-methods.js", - "end": [ - 2, - 32 - ] - } - }, - "summary": "Deleted the '{ add }' object", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "objects-with-methods.js", - "end": [ - 2, - 37 - ] - } - }, - "summary": "Added the '{ subtract }' object", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "objects-with-methods.js" - ], - "sha1": "7b8889fcf97d4f9b27d986f7dbedea7ab1b737d0", - "gitDir": "test/corpus/repos/javascript", - "sha2": "d731aac66d17f598fc601b02c4ad03adff3a3bae" -} -,{ - "testCaseDescription": "javascript-objects-with-methods-delete-test", - "expectedResult": { - "changes": { - "objects-with-methods.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "objects-with-methods.js", - "end": [ - 1, - 32 - ] - } - }, - "summary": "Deleted the '{ add }' object", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "objects-with-methods.js" - ], - "sha1": "d731aac66d17f598fc601b02c4ad03adff3a3bae", - "gitDir": "test/corpus/repos/javascript", - "sha2": "f2ac6622cd2122b9163f11890d688ac53a9bd01e" -} -,{ - "testCaseDescription": "javascript-objects-with-methods-delete-rest-test", - "expectedResult": { - "changes": { - "objects-with-methods.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "objects-with-methods.js", - "end": [ - 1, - 37 - ] - } - }, - "summary": "Deleted the '{ subtract }' object", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "objects-with-methods.js" - ], - "sha1": "f2ac6622cd2122b9163f11890d688ac53a9bd01e", - "gitDir": "test/corpus/repos/javascript", - "sha2": "71a215c337687c245da7c6eafcba311e3ba0e09b" -}] diff --git a/test/corpus/diff-summaries/javascript/object.json b/test/corpus/diff-summaries/javascript/object.json deleted file mode 100644 index 747e61990..000000000 --- a/test/corpus/diff-summaries/javascript/object.json +++ /dev/null @@ -1,316 +0,0 @@ -[{ - "testCaseDescription": "javascript-object-insert-test", - "expectedResult": { - "changes": { - "object.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "object.js", - "end": [ - 1, - 21 - ] - } - }, - "summary": "Added the '{ \"key1\": … }' object", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "object.js" - ], - "sha1": "851fcf30f6f5512f49a59cc7167c684cdf668576", - "gitDir": "test/corpus/repos/javascript", - "sha2": "8e2ca717edb3e850c87a7a5d0f4299018e008adb" -} -,{ - "testCaseDescription": "javascript-object-replacement-insert-test", - "expectedResult": { - "changes": { - "object.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "object.js", - "end": [ - 1, - 54 - ] - } - }, - "summary": "Added the '{ \"key1\": …, \"key2\": …, \"key3\": … }' object", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "object.js", - "end": [ - 2, - 21 - ] - } - }, - "summary": "Added the '{ \"key1\": … }' object", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "object.js" - ], - "sha1": "8e2ca717edb3e850c87a7a5d0f4299018e008adb", - "gitDir": "test/corpus/repos/javascript", - "sha2": "9984c70968070ad662bff6c3b00840bfaf8c1230" -} -,{ - "testCaseDescription": "javascript-object-delete-insert-test", - "expectedResult": { - "changes": { - "object.js": [ - { - "span": { - "this": { - "start": [ - 1, - 21 - ], - "name": "object.js", - "end": [ - 1, - 37 - ] - } - }, - "summary": "Deleted the '\"key2\": …' pair", - "tag": "JSONSummary" - }, - { - "span": { - "this": { - "start": [ - 1, - 39 - ], - "name": "object.js", - "end": [ - 1, - 52 - ] - } - }, - "summary": "Deleted the '\"key3\": …' pair", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "object.js" - ], - "sha1": "9984c70968070ad662bff6c3b00840bfaf8c1230", - "gitDir": "test/corpus/repos/javascript", - "sha2": "34a57cf66174002c4cb01bc2cde145af45c79bd1" -} -,{ - "testCaseDescription": "javascript-object-replacement-test", - "expectedResult": { - "changes": { - "object.js": [ - { - "span": { - "that": { - "start": [ - 1, - 21 - ], - "name": "object.js", - "end": [ - 1, - 37 - ] - } - }, - "summary": "Added the '\"key2\": …' pair", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 1, - 39 - ], - "name": "object.js", - "end": [ - 1, - 52 - ] - } - }, - "summary": "Added the '\"key3\": …' pair", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "object.js" - ], - "sha1": "34a57cf66174002c4cb01bc2cde145af45c79bd1", - "gitDir": "test/corpus/repos/javascript", - "sha2": "5212b2d89e443b54f3fa34e7f52123fe152bed71" -} -,{ - "testCaseDescription": "javascript-object-delete-replacement-test", - "expectedResult": { - "changes": { - "object.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "object.js", - "end": [ - 1, - 54 - ] - } - }, - "summary": "Deleted the '{ \"key1\": …, \"key2\": …, \"key3\": … }' object", - "tag": "JSONSummary" - }, - { - "span": { - "this": { - "start": [ - 2, - 1 - ], - "name": "object.js", - "end": [ - 2, - 21 - ] - } - }, - "summary": "Deleted the '{ \"key1\": … }' object", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "object.js", - "end": [ - 2, - 54 - ] - } - }, - "summary": "Added the '{ \"key1\": …, \"key2\": …, \"key3\": … }' object", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "object.js" - ], - "sha1": "5212b2d89e443b54f3fa34e7f52123fe152bed71", - "gitDir": "test/corpus/repos/javascript", - "sha2": "aa3e5600050b3762cdf02c85bdd7c6c91c52896e" -} -,{ - "testCaseDescription": "javascript-object-delete-test", - "expectedResult": { - "changes": { - "object.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "object.js", - "end": [ - 1, - 21 - ] - } - }, - "summary": "Deleted the '{ \"key1\": … }' object", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "object.js" - ], - "sha1": "aa3e5600050b3762cdf02c85bdd7c6c91c52896e", - "gitDir": "test/corpus/repos/javascript", - "sha2": "ffbe546c27f8f46e1c56d5d60f298870b4afe943" -} -,{ - "testCaseDescription": "javascript-object-delete-rest-test", - "expectedResult": { - "changes": { - "object.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "object.js", - "end": [ - 1, - 54 - ] - } - }, - "summary": "Deleted the '{ \"key1\": …, \"key2\": …, \"key3\": … }' object", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "object.js" - ], - "sha1": "ffbe546c27f8f46e1c56d5d60f298870b4afe943", - "gitDir": "test/corpus/repos/javascript", - "sha2": "4e616c4976a8cc24c20fda3c6bfcde4cfa22483f" -}] diff --git a/test/corpus/diff-summaries/javascript/regex.json b/test/corpus/diff-summaries/javascript/regex.json deleted file mode 100644 index 15ecde5db..000000000 --- a/test/corpus/diff-summaries/javascript/regex.json +++ /dev/null @@ -1,308 +0,0 @@ -[{ - "testCaseDescription": "javascript-regex-insert-test", - "expectedResult": { - "changes": { - "regex.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "regex.js", - "end": [ - 1, - 7 - ] - } - }, - "summary": "Added the '/one/g' regex", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "regex.js" - ], - "sha1": "87a75eabc61b58f15583babf507419181ab63aeb", - "gitDir": "test/corpus/repos/javascript", - "sha2": "650dad8817cc6e81699795ce01d6f55f47ee8467" -} -,{ - "testCaseDescription": "javascript-regex-replacement-insert-test", - "expectedResult": { - "changes": { - "regex.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "regex.js", - "end": [ - 1, - 15 - ] - } - }, - "summary": "Added the '/on[^/]afe/gim' regex", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "regex.js", - "end": [ - 2, - 7 - ] - } - }, - "summary": "Added the '/one/g' regex", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "regex.js" - ], - "sha1": "650dad8817cc6e81699795ce01d6f55f47ee8467", - "gitDir": "test/corpus/repos/javascript", - "sha2": "6ccce2bf1a0492d851f6a12566b7eecabbc53e7c" -} -,{ - "testCaseDescription": "javascript-regex-delete-insert-test", - "expectedResult": { - "changes": { - "regex.js": [ - { - "span": { - "these": [ - { - "start": [ - 1, - 1 - ], - "name": "regex.js", - "end": [ - 1, - 15 - ] - }, - { - "start": [ - 1, - 1 - ], - "name": "regex.js", - "end": [ - 1, - 7 - ] - } - ] - }, - "summary": "Replaced the '/on[^/]afe/gim' regex with the '/one/g' regex", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "regex.js" - ], - "sha1": "6ccce2bf1a0492d851f6a12566b7eecabbc53e7c", - "gitDir": "test/corpus/repos/javascript", - "sha2": "20edafc45d28234ef35c2f4ac6c5f3b72a9e178a" -} -,{ - "testCaseDescription": "javascript-regex-replacement-test", - "expectedResult": { - "changes": { - "regex.js": [ - { - "span": { - "these": [ - { - "start": [ - 1, - 1 - ], - "name": "regex.js", - "end": [ - 1, - 7 - ] - }, - { - "start": [ - 1, - 1 - ], - "name": "regex.js", - "end": [ - 1, - 15 - ] - } - ] - }, - "summary": "Replaced the '/one/g' regex with the '/on[^/]afe/gim' regex", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "regex.js" - ], - "sha1": "20edafc45d28234ef35c2f4ac6c5f3b72a9e178a", - "gitDir": "test/corpus/repos/javascript", - "sha2": "3f6396c441334c8beaa3819e7b6cdb44196341c3" -} -,{ - "testCaseDescription": "javascript-regex-delete-replacement-test", - "expectedResult": { - "changes": { - "regex.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "regex.js", - "end": [ - 1, - 15 - ] - } - }, - "summary": "Deleted the '/on[^/]afe/gim' regex", - "tag": "JSONSummary" - }, - { - "span": { - "this": { - "start": [ - 2, - 1 - ], - "name": "regex.js", - "end": [ - 2, - 7 - ] - } - }, - "summary": "Deleted the '/one/g' regex", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "regex.js", - "end": [ - 2, - 15 - ] - } - }, - "summary": "Added the '/on[^/]afe/gim' regex", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "regex.js" - ], - "sha1": "3f6396c441334c8beaa3819e7b6cdb44196341c3", - "gitDir": "test/corpus/repos/javascript", - "sha2": "a09af80adb555a0c9c30839fbe7014942bfcf449" -} -,{ - "testCaseDescription": "javascript-regex-delete-test", - "expectedResult": { - "changes": { - "regex.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "regex.js", - "end": [ - 1, - 7 - ] - } - }, - "summary": "Deleted the '/one/g' regex", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "regex.js" - ], - "sha1": "a09af80adb555a0c9c30839fbe7014942bfcf449", - "gitDir": "test/corpus/repos/javascript", - "sha2": "e0e94d4e600134f55d47ad0fbdea6f791be2e618" -} -,{ - "testCaseDescription": "javascript-regex-delete-rest-test", - "expectedResult": { - "changes": { - "regex.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "regex.js", - "end": [ - 1, - 15 - ] - } - }, - "summary": "Deleted the '/on[^/]afe/gim' regex", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "regex.js" - ], - "sha1": "e0e94d4e600134f55d47ad0fbdea6f791be2e618", - "gitDir": "test/corpus/repos/javascript", - "sha2": "408411b4e79d51cf3b50541c8d1115a3ce46dfa8" -}] diff --git a/test/corpus/diff-summaries/javascript/relational-operator.json b/test/corpus/diff-summaries/javascript/relational-operator.json deleted file mode 100644 index d5057eed0..000000000 --- a/test/corpus/diff-summaries/javascript/relational-operator.json +++ /dev/null @@ -1,208 +0,0 @@ -[{ - "testCaseDescription": "javascript-relational-operator-insert-test", - "expectedResult": { - "changes": { - "relational-operator.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "relational-operator.js", - "end": [ - 1, - 6 - ] - } - }, - "summary": "Added the 'x < y' relational operator", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "relational-operator.js" - ], - "sha1": "8cdb0cc77bfe88b76c86dcde66d08f97f11182f3", - "gitDir": "test/corpus/repos/javascript", - "sha2": "da2638f6fc96de8b58f104e1db1d5a665b5e3a9b" -} -,{ - "testCaseDescription": "javascript-relational-operator-replacement-insert-test", - "expectedResult": { - "changes": { - "relational-operator.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "relational-operator.js", - "end": [ - 1, - 7 - ] - } - }, - "summary": "Added the 'x <= y' relational operator", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "relational-operator.js", - "end": [ - 2, - 6 - ] - } - }, - "summary": "Added the 'x < y' relational operator", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "relational-operator.js" - ], - "sha1": "da2638f6fc96de8b58f104e1db1d5a665b5e3a9b", - "gitDir": "test/corpus/repos/javascript", - "sha2": "95ef181dcd3fc26ed54bf60bfd60447a51c8ffd7" -} -,{ - "testCaseDescription": "javascript-relational-operator-delete-insert-test", - "expectedResult": { - "changes": {}, - "errors": {} - }, - "filePaths": [ - "relational-operator.js" - ], - "sha1": "95ef181dcd3fc26ed54bf60bfd60447a51c8ffd7", - "gitDir": "test/corpus/repos/javascript", - "sha2": "d3346f7942edffe06e10ca06433091c89a815a74" -} -,{ - "testCaseDescription": "javascript-relational-operator-replacement-test", - "expectedResult": { - "changes": {}, - "errors": {} - }, - "filePaths": [ - "relational-operator.js" - ], - "sha1": "d3346f7942edffe06e10ca06433091c89a815a74", - "gitDir": "test/corpus/repos/javascript", - "sha2": "8b110a7eeb3d75ad831ec61d91539bb3110a5c82" -} -,{ - "testCaseDescription": "javascript-relational-operator-delete-replacement-test", - "expectedResult": { - "changes": { - "relational-operator.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "relational-operator.js", - "end": [ - 1, - 7 - ] - } - }, - "summary": "Deleted the 'x <= y' relational operator", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "relational-operator.js" - ], - "sha1": "8b110a7eeb3d75ad831ec61d91539bb3110a5c82", - "gitDir": "test/corpus/repos/javascript", - "sha2": "02d3364197afdd61f67f2e693ae3a8d09c64560f" -} -,{ - "testCaseDescription": "javascript-relational-operator-delete-test", - "expectedResult": { - "changes": { - "relational-operator.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "relational-operator.js", - "end": [ - 1, - 6 - ] - } - }, - "summary": "Deleted the 'x < y' relational operator", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "relational-operator.js" - ], - "sha1": "02d3364197afdd61f67f2e693ae3a8d09c64560f", - "gitDir": "test/corpus/repos/javascript", - "sha2": "59255aa8bf840f1bf5dc446a5c4190a538be2f13" -} -,{ - "testCaseDescription": "javascript-relational-operator-delete-rest-test", - "expectedResult": { - "changes": { - "relational-operator.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "relational-operator.js", - "end": [ - 1, - 7 - ] - } - }, - "summary": "Deleted the 'x <= y' relational operator", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "relational-operator.js" - ], - "sha1": "59255aa8bf840f1bf5dc446a5c4190a538be2f13", - "gitDir": "test/corpus/repos/javascript", - "sha2": "761990749004312c4b5e474eeacb839376523f0b" -}] diff --git a/test/corpus/diff-summaries/javascript/return-statement.json b/test/corpus/diff-summaries/javascript/return-statement.json deleted file mode 100644 index 732bbe3f3..000000000 --- a/test/corpus/diff-summaries/javascript/return-statement.json +++ /dev/null @@ -1,282 +0,0 @@ -[{ - "testCaseDescription": "javascript-return-statement-insert-test", - "expectedResult": { - "changes": { - "return-statement.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "return-statement.js", - "end": [ - 1, - 10 - ] - } - }, - "summary": "Added the '5' return statement", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "return-statement.js" - ], - "sha1": "a6c49cc7711970d9b1fdcfeef8ea1b312bcf0ace", - "gitDir": "test/corpus/repos/javascript", - "sha2": "cce29acfef026dd830249e9d1336513f6e3c4304" -} -,{ - "testCaseDescription": "javascript-return-statement-replacement-insert-test", - "expectedResult": { - "changes": { - "return-statement.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "return-statement.js", - "end": [ - 1, - 8 - ] - } - }, - "summary": "Added the 'empty' return statement", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "return-statement.js", - "end": [ - 2, - 10 - ] - } - }, - "summary": "Added the '5' return statement", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "return-statement.js" - ], - "sha1": "cce29acfef026dd830249e9d1336513f6e3c4304", - "gitDir": "test/corpus/repos/javascript", - "sha2": "c8de458d3d17e648dfbf1869bb0b1ce2e0979601" -} -,{ - "testCaseDescription": "javascript-return-statement-delete-insert-test", - "expectedResult": { - "changes": { - "return-statement.js": [ - { - "span": { - "that": { - "start": [ - 1, - 8 - ], - "name": "return-statement.js", - "end": [ - 1, - 9 - ] - } - }, - "summary": "Added '5'", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "return-statement.js" - ], - "sha1": "c8de458d3d17e648dfbf1869bb0b1ce2e0979601", - "gitDir": "test/corpus/repos/javascript", - "sha2": "1ec1da945159b2908ed73826fa61ed65680b7ab0" -} -,{ - "testCaseDescription": "javascript-return-statement-replacement-test", - "expectedResult": { - "changes": { - "return-statement.js": [ - { - "span": { - "this": { - "start": [ - 1, - 8 - ], - "name": "return-statement.js", - "end": [ - 1, - 9 - ] - } - }, - "summary": "Deleted '5'", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "return-statement.js" - ], - "sha1": "1ec1da945159b2908ed73826fa61ed65680b7ab0", - "gitDir": "test/corpus/repos/javascript", - "sha2": "d942adb626ca42c2407c698701c173fcf1215775" -} -,{ - "testCaseDescription": "javascript-return-statement-delete-replacement-test", - "expectedResult": { - "changes": { - "return-statement.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "return-statement.js", - "end": [ - 1, - 8 - ] - } - }, - "summary": "Deleted the 'empty' return statement", - "tag": "JSONSummary" - }, - { - "span": { - "this": { - "start": [ - 2, - 1 - ], - "name": "return-statement.js", - "end": [ - 2, - 10 - ] - } - }, - "summary": "Deleted the '5' return statement", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "return-statement.js", - "end": [ - 2, - 8 - ] - } - }, - "summary": "Added the 'empty' return statement", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "return-statement.js" - ], - "sha1": "d942adb626ca42c2407c698701c173fcf1215775", - "gitDir": "test/corpus/repos/javascript", - "sha2": "d4af520a89d43ed45e2ab60753d6b5e0542c2812" -} -,{ - "testCaseDescription": "javascript-return-statement-delete-test", - "expectedResult": { - "changes": { - "return-statement.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "return-statement.js", - "end": [ - 1, - 10 - ] - } - }, - "summary": "Deleted the '5' return statement", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "return-statement.js" - ], - "sha1": "d4af520a89d43ed45e2ab60753d6b5e0542c2812", - "gitDir": "test/corpus/repos/javascript", - "sha2": "006d0dd9f64dfec01d6a4027448f81864951fc14" -} -,{ - "testCaseDescription": "javascript-return-statement-delete-rest-test", - "expectedResult": { - "changes": { - "return-statement.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "return-statement.js", - "end": [ - 1, - 8 - ] - } - }, - "summary": "Deleted the 'empty' return statement", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "return-statement.js" - ], - "sha1": "006d0dd9f64dfec01d6a4027448f81864951fc14", - "gitDir": "test/corpus/repos/javascript", - "sha2": "a5fb0a1bf511cc98cae35a20ea3a6dad064448bc" -}] diff --git a/test/corpus/diff-summaries/javascript/string.json b/test/corpus/diff-summaries/javascript/string.json deleted file mode 100644 index 76fc97c66..000000000 --- a/test/corpus/diff-summaries/javascript/string.json +++ /dev/null @@ -1,308 +0,0 @@ -[{ - "testCaseDescription": "javascript-string-insert-test", - "expectedResult": { - "changes": { - "string.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "string.js", - "end": [ - 1, - 32 - ] - } - }, - "summary": "Added the 'A string with \"double\" quotes' string", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "string.js" - ], - "sha1": "71a215c337687c245da7c6eafcba311e3ba0e09b", - "gitDir": "test/corpus/repos/javascript", - "sha2": "890f6940b147be1142451548897bb522f2cc0e0e" -} -,{ - "testCaseDescription": "javascript-string-replacement-insert-test", - "expectedResult": { - "changes": { - "string.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "string.js", - "end": [ - 1, - 42 - ] - } - }, - "summary": "Added the 'A different string with \"double\" quotes' string", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "string.js", - "end": [ - 2, - 32 - ] - } - }, - "summary": "Added the 'A string with \"double\" quotes' string", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "string.js" - ], - "sha1": "890f6940b147be1142451548897bb522f2cc0e0e", - "gitDir": "test/corpus/repos/javascript", - "sha2": "a1bd8ab3294f256b512c1c8f2e71e36f5382c5dc" -} -,{ - "testCaseDescription": "javascript-string-delete-insert-test", - "expectedResult": { - "changes": { - "string.js": [ - { - "span": { - "these": [ - { - "start": [ - 1, - 1 - ], - "name": "string.js", - "end": [ - 1, - 42 - ] - }, - { - "start": [ - 1, - 1 - ], - "name": "string.js", - "end": [ - 1, - 32 - ] - } - ] - }, - "summary": "Replaced the 'A different string with \"double\" quotes' string with the 'A string with \"double\" quotes' string", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "string.js" - ], - "sha1": "a1bd8ab3294f256b512c1c8f2e71e36f5382c5dc", - "gitDir": "test/corpus/repos/javascript", - "sha2": "6965b973b84c4170ec98730272475e697686d29e" -} -,{ - "testCaseDescription": "javascript-string-replacement-test", - "expectedResult": { - "changes": { - "string.js": [ - { - "span": { - "these": [ - { - "start": [ - 1, - 1 - ], - "name": "string.js", - "end": [ - 1, - 32 - ] - }, - { - "start": [ - 1, - 1 - ], - "name": "string.js", - "end": [ - 1, - 42 - ] - } - ] - }, - "summary": "Replaced the 'A string with \"double\" quotes' string with the 'A different string with \"double\" quotes' string", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "string.js" - ], - "sha1": "6965b973b84c4170ec98730272475e697686d29e", - "gitDir": "test/corpus/repos/javascript", - "sha2": "92a860f5c70f4aa4da65a6919a026b01d717804c" -} -,{ - "testCaseDescription": "javascript-string-delete-replacement-test", - "expectedResult": { - "changes": { - "string.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "string.js", - "end": [ - 1, - 42 - ] - } - }, - "summary": "Deleted the 'A different string with \"double\" quotes' string", - "tag": "JSONSummary" - }, - { - "span": { - "this": { - "start": [ - 2, - 1 - ], - "name": "string.js", - "end": [ - 2, - 32 - ] - } - }, - "summary": "Deleted the 'A string with \"double\" quotes' string", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "string.js", - "end": [ - 2, - 42 - ] - } - }, - "summary": "Added the 'A different string with \"double\" quotes' string", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "string.js" - ], - "sha1": "92a860f5c70f4aa4da65a6919a026b01d717804c", - "gitDir": "test/corpus/repos/javascript", - "sha2": "27d40a59d34bcf26ccd02b06f857c20f85a9df41" -} -,{ - "testCaseDescription": "javascript-string-delete-test", - "expectedResult": { - "changes": { - "string.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "string.js", - "end": [ - 1, - 32 - ] - } - }, - "summary": "Deleted the 'A string with \"double\" quotes' string", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "string.js" - ], - "sha1": "27d40a59d34bcf26ccd02b06f857c20f85a9df41", - "gitDir": "test/corpus/repos/javascript", - "sha2": "b18bf04fd766cc584977cd2ba38b84199ab2f62d" -} -,{ - "testCaseDescription": "javascript-string-delete-rest-test", - "expectedResult": { - "changes": { - "string.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "string.js", - "end": [ - 1, - 42 - ] - } - }, - "summary": "Deleted the 'A different string with \"double\" quotes' string", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "string.js" - ], - "sha1": "b18bf04fd766cc584977cd2ba38b84199ab2f62d", - "gitDir": "test/corpus/repos/javascript", - "sha2": "6353fa1218bad4624b606cf46bfcd6c18d1e13c2" -}] diff --git a/test/corpus/diff-summaries/javascript/subscript-access-assignment.json b/test/corpus/diff-summaries/javascript/subscript-access-assignment.json deleted file mode 100644 index 277f48e77..000000000 --- a/test/corpus/diff-summaries/javascript/subscript-access-assignment.json +++ /dev/null @@ -1,308 +0,0 @@ -[{ - "testCaseDescription": "javascript-subscript-access-assignment-insert-test", - "expectedResult": { - "changes": { - "subscript-access-assignment.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "subscript-access-assignment.js", - "end": [ - 1, - 11 - ] - } - }, - "summary": "Added the 'y[\"x\"]' assignment", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "subscript-access-assignment.js" - ], - "sha1": "0286a0f0ca80520eb670a372dbf844ec8357639e", - "gitDir": "test/corpus/repos/javascript", - "sha2": "8303b810d953c09eec10797a00b3ab66d923e510" -} -,{ - "testCaseDescription": "javascript-subscript-access-assignment-replacement-insert-test", - "expectedResult": { - "changes": { - "subscript-access-assignment.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "subscript-access-assignment.js", - "end": [ - 1, - 11 - ] - } - }, - "summary": "Added the 'y[\"x\"]' assignment", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "subscript-access-assignment.js", - "end": [ - 2, - 11 - ] - } - }, - "summary": "Added the 'y[\"x\"]' assignment", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "subscript-access-assignment.js" - ], - "sha1": "8303b810d953c09eec10797a00b3ab66d923e510", - "gitDir": "test/corpus/repos/javascript", - "sha2": "3db24d6ecd3ac85657b5c13192208dbc4a86a6bf" -} -,{ - "testCaseDescription": "javascript-subscript-access-assignment-delete-insert-test", - "expectedResult": { - "changes": { - "subscript-access-assignment.js": [ - { - "span": { - "these": [ - { - "start": [ - 1, - 10 - ], - "name": "subscript-access-assignment.js", - "end": [ - 1, - 11 - ] - }, - { - "start": [ - 1, - 10 - ], - "name": "subscript-access-assignment.js", - "end": [ - 1, - 11 - ] - } - ] - }, - "summary": "Replaced '1' with '0' in an assignment to y[\"x\"]", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "subscript-access-assignment.js" - ], - "sha1": "3db24d6ecd3ac85657b5c13192208dbc4a86a6bf", - "gitDir": "test/corpus/repos/javascript", - "sha2": "3a74a00c6e3ef58372e16138057561bbdaaa9e09" -} -,{ - "testCaseDescription": "javascript-subscript-access-assignment-replacement-test", - "expectedResult": { - "changes": { - "subscript-access-assignment.js": [ - { - "span": { - "these": [ - { - "start": [ - 1, - 10 - ], - "name": "subscript-access-assignment.js", - "end": [ - 1, - 11 - ] - }, - { - "start": [ - 1, - 10 - ], - "name": "subscript-access-assignment.js", - "end": [ - 1, - 11 - ] - } - ] - }, - "summary": "Replaced '0' with '1' in an assignment to y[\"x\"]", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "subscript-access-assignment.js" - ], - "sha1": "3a74a00c6e3ef58372e16138057561bbdaaa9e09", - "gitDir": "test/corpus/repos/javascript", - "sha2": "59489169d3ee84ebaebab0a32db21de5feda9b9b" -} -,{ - "testCaseDescription": "javascript-subscript-access-assignment-delete-replacement-test", - "expectedResult": { - "changes": { - "subscript-access-assignment.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "subscript-access-assignment.js", - "end": [ - 1, - 11 - ] - } - }, - "summary": "Deleted the 'y[\"x\"]' assignment", - "tag": "JSONSummary" - }, - { - "span": { - "this": { - "start": [ - 2, - 1 - ], - "name": "subscript-access-assignment.js", - "end": [ - 2, - 11 - ] - } - }, - "summary": "Deleted the 'y[\"x\"]' assignment", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "subscript-access-assignment.js", - "end": [ - 2, - 11 - ] - } - }, - "summary": "Added the 'y[\"x\"]' assignment", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "subscript-access-assignment.js" - ], - "sha1": "59489169d3ee84ebaebab0a32db21de5feda9b9b", - "gitDir": "test/corpus/repos/javascript", - "sha2": "37120ecde944db661969f1cedbda2aa0796858eb" -} -,{ - "testCaseDescription": "javascript-subscript-access-assignment-delete-test", - "expectedResult": { - "changes": { - "subscript-access-assignment.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "subscript-access-assignment.js", - "end": [ - 1, - 11 - ] - } - }, - "summary": "Deleted the 'y[\"x\"]' assignment", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "subscript-access-assignment.js" - ], - "sha1": "37120ecde944db661969f1cedbda2aa0796858eb", - "gitDir": "test/corpus/repos/javascript", - "sha2": "8632cbda9073b25b4a495c242641b1eb01d4a260" -} -,{ - "testCaseDescription": "javascript-subscript-access-assignment-delete-rest-test", - "expectedResult": { - "changes": { - "subscript-access-assignment.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "subscript-access-assignment.js", - "end": [ - 1, - 11 - ] - } - }, - "summary": "Deleted the 'y[\"x\"]' assignment", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "subscript-access-assignment.js" - ], - "sha1": "8632cbda9073b25b4a495c242641b1eb01d4a260", - "gitDir": "test/corpus/repos/javascript", - "sha2": "ea966e7428b15b541246b765517db3f0ef1c6af8" -}] diff --git a/test/corpus/diff-summaries/javascript/subscript-access-string.json b/test/corpus/diff-summaries/javascript/subscript-access-string.json deleted file mode 100644 index f8120c282..000000000 --- a/test/corpus/diff-summaries/javascript/subscript-access-string.json +++ /dev/null @@ -1,308 +0,0 @@ -[{ - "testCaseDescription": "javascript-subscript-access-string-insert-test", - "expectedResult": { - "changes": { - "subscript-access-string.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "subscript-access-string.js", - "end": [ - 1, - 17 - ] - } - }, - "summary": "Added the 'x[\"some-string\"]' subscript access", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "subscript-access-string.js" - ], - "sha1": "b5a7a5a17e38194441efeaf2ddc572cf612a050c", - "gitDir": "test/corpus/repos/javascript", - "sha2": "ab035d165637ae2f6549f91b23cb3d8397086a5b" -} -,{ - "testCaseDescription": "javascript-subscript-access-string-replacement-insert-test", - "expectedResult": { - "changes": { - "subscript-access-string.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "subscript-access-string.js", - "end": [ - 1, - 23 - ] - } - }, - "summary": "Added the 'x[\"some-other-string\"]' subscript access", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "subscript-access-string.js", - "end": [ - 2, - 17 - ] - } - }, - "summary": "Added the 'x[\"some-string\"]' subscript access", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "subscript-access-string.js" - ], - "sha1": "ab035d165637ae2f6549f91b23cb3d8397086a5b", - "gitDir": "test/corpus/repos/javascript", - "sha2": "6a0dd5ec60be73dd88995bbf2fc987895204fd69" -} -,{ - "testCaseDescription": "javascript-subscript-access-string-delete-insert-test", - "expectedResult": { - "changes": { - "subscript-access-string.js": [ - { - "span": { - "these": [ - { - "start": [ - 1, - 3 - ], - "name": "subscript-access-string.js", - "end": [ - 1, - 22 - ] - }, - { - "start": [ - 1, - 3 - ], - "name": "subscript-access-string.js", - "end": [ - 1, - 16 - ] - } - ] - }, - "summary": "Replaced the \"some-other-string\" string with the \"some-string\" string in the x[\"some-string\"] subscript access", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "subscript-access-string.js" - ], - "sha1": "6a0dd5ec60be73dd88995bbf2fc987895204fd69", - "gitDir": "test/corpus/repos/javascript", - "sha2": "cf1ef60479b2d9c834590a4c6f4f7717a657e1cd" -} -,{ - "testCaseDescription": "javascript-subscript-access-string-replacement-test", - "expectedResult": { - "changes": { - "subscript-access-string.js": [ - { - "span": { - "these": [ - { - "start": [ - 1, - 3 - ], - "name": "subscript-access-string.js", - "end": [ - 1, - 16 - ] - }, - { - "start": [ - 1, - 3 - ], - "name": "subscript-access-string.js", - "end": [ - 1, - 22 - ] - } - ] - }, - "summary": "Replaced the \"some-string\" string with the \"some-other-string\" string in the x[\"some-other-string\"] subscript access", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "subscript-access-string.js" - ], - "sha1": "cf1ef60479b2d9c834590a4c6f4f7717a657e1cd", - "gitDir": "test/corpus/repos/javascript", - "sha2": "c476a25c1998c3c480523c8179b29584ad2e00a3" -} -,{ - "testCaseDescription": "javascript-subscript-access-string-delete-replacement-test", - "expectedResult": { - "changes": { - "subscript-access-string.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "subscript-access-string.js", - "end": [ - 1, - 23 - ] - } - }, - "summary": "Deleted the 'x[\"some-other-string\"]' subscript access", - "tag": "JSONSummary" - }, - { - "span": { - "this": { - "start": [ - 2, - 1 - ], - "name": "subscript-access-string.js", - "end": [ - 2, - 17 - ] - } - }, - "summary": "Deleted the 'x[\"some-string\"]' subscript access", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "subscript-access-string.js", - "end": [ - 2, - 23 - ] - } - }, - "summary": "Added the 'x[\"some-other-string\"]' subscript access", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "subscript-access-string.js" - ], - "sha1": "c476a25c1998c3c480523c8179b29584ad2e00a3", - "gitDir": "test/corpus/repos/javascript", - "sha2": "2f049bd94a6e832b099c647e31ee0a028fa26051" -} -,{ - "testCaseDescription": "javascript-subscript-access-string-delete-test", - "expectedResult": { - "changes": { - "subscript-access-string.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "subscript-access-string.js", - "end": [ - 1, - 17 - ] - } - }, - "summary": "Deleted the 'x[\"some-string\"]' subscript access", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "subscript-access-string.js" - ], - "sha1": "2f049bd94a6e832b099c647e31ee0a028fa26051", - "gitDir": "test/corpus/repos/javascript", - "sha2": "a88fd09203e1ffb45ef9d0b5a916150099d2f0d7" -} -,{ - "testCaseDescription": "javascript-subscript-access-string-delete-rest-test", - "expectedResult": { - "changes": { - "subscript-access-string.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "subscript-access-string.js", - "end": [ - 1, - 23 - ] - } - }, - "summary": "Deleted the 'x[\"some-other-string\"]' subscript access", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "subscript-access-string.js" - ], - "sha1": "a88fd09203e1ffb45ef9d0b5a916150099d2f0d7", - "gitDir": "test/corpus/repos/javascript", - "sha2": "07c5dd47cd837cd06d7d034c049ea6002a5e0980" -}] diff --git a/test/corpus/diff-summaries/javascript/subscript-access-variable.json b/test/corpus/diff-summaries/javascript/subscript-access-variable.json deleted file mode 100644 index 3140c1e63..000000000 --- a/test/corpus/diff-summaries/javascript/subscript-access-variable.json +++ /dev/null @@ -1,308 +0,0 @@ -[{ - "testCaseDescription": "javascript-subscript-access-variable-insert-test", - "expectedResult": { - "changes": { - "subscript-access-variable.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "subscript-access-variable.js", - "end": [ - 1, - 16 - ] - } - }, - "summary": "Added the 'x[someVariable]' subscript access", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "subscript-access-variable.js" - ], - "sha1": "c77d21ce31ff19818614b186e90aa577cc20ce9d", - "gitDir": "test/corpus/repos/javascript", - "sha2": "4d5dda84d5715cb19e8562fa86ec775ad7bc3b52" -} -,{ - "testCaseDescription": "javascript-subscript-access-variable-replacement-insert-test", - "expectedResult": { - "changes": { - "subscript-access-variable.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "subscript-access-variable.js", - "end": [ - 1, - 21 - ] - } - }, - "summary": "Added the 'x[someOtherVariable]' subscript access", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "subscript-access-variable.js", - "end": [ - 2, - 16 - ] - } - }, - "summary": "Added the 'x[someVariable]' subscript access", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "subscript-access-variable.js" - ], - "sha1": "4d5dda84d5715cb19e8562fa86ec775ad7bc3b52", - "gitDir": "test/corpus/repos/javascript", - "sha2": "a73be8ec6fa12c27b78977f88cde47c3131f85a0" -} -,{ - "testCaseDescription": "javascript-subscript-access-variable-delete-insert-test", - "expectedResult": { - "changes": { - "subscript-access-variable.js": [ - { - "span": { - "these": [ - { - "start": [ - 1, - 3 - ], - "name": "subscript-access-variable.js", - "end": [ - 1, - 20 - ] - }, - { - "start": [ - 1, - 3 - ], - "name": "subscript-access-variable.js", - "end": [ - 1, - 15 - ] - } - ] - }, - "summary": "Replaced the 'someOtherVariable' identifier with the 'someVariable' identifier in the x[someVariable] subscript access", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "subscript-access-variable.js" - ], - "sha1": "a73be8ec6fa12c27b78977f88cde47c3131f85a0", - "gitDir": "test/corpus/repos/javascript", - "sha2": "b1f52c7fa0096992d231a1a96f2d3c6bd350a948" -} -,{ - "testCaseDescription": "javascript-subscript-access-variable-replacement-test", - "expectedResult": { - "changes": { - "subscript-access-variable.js": [ - { - "span": { - "these": [ - { - "start": [ - 1, - 3 - ], - "name": "subscript-access-variable.js", - "end": [ - 1, - 15 - ] - }, - { - "start": [ - 1, - 3 - ], - "name": "subscript-access-variable.js", - "end": [ - 1, - 20 - ] - } - ] - }, - "summary": "Replaced the 'someVariable' identifier with the 'someOtherVariable' identifier in the x[someOtherVariable] subscript access", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "subscript-access-variable.js" - ], - "sha1": "b1f52c7fa0096992d231a1a96f2d3c6bd350a948", - "gitDir": "test/corpus/repos/javascript", - "sha2": "d7d36537db64ed980915c9fd7438eb28aca9121a" -} -,{ - "testCaseDescription": "javascript-subscript-access-variable-delete-replacement-test", - "expectedResult": { - "changes": { - "subscript-access-variable.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "subscript-access-variable.js", - "end": [ - 1, - 21 - ] - } - }, - "summary": "Deleted the 'x[someOtherVariable]' subscript access", - "tag": "JSONSummary" - }, - { - "span": { - "this": { - "start": [ - 2, - 1 - ], - "name": "subscript-access-variable.js", - "end": [ - 2, - 16 - ] - } - }, - "summary": "Deleted the 'x[someVariable]' subscript access", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "subscript-access-variable.js", - "end": [ - 2, - 21 - ] - } - }, - "summary": "Added the 'x[someOtherVariable]' subscript access", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "subscript-access-variable.js" - ], - "sha1": "d7d36537db64ed980915c9fd7438eb28aca9121a", - "gitDir": "test/corpus/repos/javascript", - "sha2": "39e4553a4dc76006a19f6907144fe12affe9b3bf" -} -,{ - "testCaseDescription": "javascript-subscript-access-variable-delete-test", - "expectedResult": { - "changes": { - "subscript-access-variable.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "subscript-access-variable.js", - "end": [ - 1, - 16 - ] - } - }, - "summary": "Deleted the 'x[someVariable]' subscript access", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "subscript-access-variable.js" - ], - "sha1": "39e4553a4dc76006a19f6907144fe12affe9b3bf", - "gitDir": "test/corpus/repos/javascript", - "sha2": "579578d94e6d3639fef8ef66a5c71d990e4f7a95" -} -,{ - "testCaseDescription": "javascript-subscript-access-variable-delete-rest-test", - "expectedResult": { - "changes": { - "subscript-access-variable.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "subscript-access-variable.js", - "end": [ - 1, - 21 - ] - } - }, - "summary": "Deleted the 'x[someOtherVariable]' subscript access", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "subscript-access-variable.js" - ], - "sha1": "579578d94e6d3639fef8ef66a5c71d990e4f7a95", - "gitDir": "test/corpus/repos/javascript", - "sha2": "b5a7a5a17e38194441efeaf2ddc572cf612a050c" -}] diff --git a/test/corpus/diff-summaries/javascript/switch-statement.json b/test/corpus/diff-summaries/javascript/switch-statement.json deleted file mode 100644 index c070de7a0..000000000 --- a/test/corpus/diff-summaries/javascript/switch-statement.json +++ /dev/null @@ -1,368 +0,0 @@ -[{ - "testCaseDescription": "javascript-switch-statement-insert-test", - "expectedResult": { - "changes": { - "switch-statement.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "switch-statement.js", - "end": [ - 1, - 48 - ] - } - }, - "summary": "Added the '1' switch statement", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "switch-statement.js" - ], - "sha1": "df276ed5f435d4cf1363008ae573ea99ba39e175", - "gitDir": "test/corpus/repos/javascript", - "sha2": "e906cd9ad5ab469f68df1fd23910bbe78a9f8cd1" -} -,{ - "testCaseDescription": "javascript-switch-statement-replacement-insert-test", - "expectedResult": { - "changes": { - "switch-statement.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "switch-statement.js", - "end": [ - 1, - 48 - ] - } - }, - "summary": "Added the '2' switch statement", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "switch-statement.js", - "end": [ - 2, - 48 - ] - } - }, - "summary": "Added the '1' switch statement", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "switch-statement.js" - ], - "sha1": "e906cd9ad5ab469f68df1fd23910bbe78a9f8cd1", - "gitDir": "test/corpus/repos/javascript", - "sha2": "b5602de388c92c96c7f62e0fcf1cce07b403c185" -} -,{ - "testCaseDescription": "javascript-switch-statement-delete-insert-test", - "expectedResult": { - "changes": { - "switch-statement.js": [ - { - "span": { - "these": [ - { - "start": [ - 1, - 9 - ], - "name": "switch-statement.js", - "end": [ - 1, - 10 - ] - }, - { - "start": [ - 1, - 9 - ], - "name": "switch-statement.js", - "end": [ - 1, - 10 - ] - } - ] - }, - "summary": "Replaced '2' with '1'", - "tag": "JSONSummary" - }, - { - "span": { - "these": [ - { - "start": [ - 1, - 33 - ], - "name": "switch-statement.js", - "end": [ - 1, - 34 - ] - }, - { - "start": [ - 1, - 33 - ], - "name": "switch-statement.js", - "end": [ - 1, - 34 - ] - } - ] - }, - "summary": "Replaced '2' with '1'", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "switch-statement.js" - ], - "sha1": "b5602de388c92c96c7f62e0fcf1cce07b403c185", - "gitDir": "test/corpus/repos/javascript", - "sha2": "fa74d55721267c11d2be5de262e9eb3100ba91f0" -} -,{ - "testCaseDescription": "javascript-switch-statement-replacement-test", - "expectedResult": { - "changes": { - "switch-statement.js": [ - { - "span": { - "these": [ - { - "start": [ - 1, - 9 - ], - "name": "switch-statement.js", - "end": [ - 1, - 10 - ] - }, - { - "start": [ - 1, - 9 - ], - "name": "switch-statement.js", - "end": [ - 1, - 10 - ] - } - ] - }, - "summary": "Replaced '1' with '2'", - "tag": "JSONSummary" - }, - { - "span": { - "these": [ - { - "start": [ - 1, - 33 - ], - "name": "switch-statement.js", - "end": [ - 1, - 34 - ] - }, - { - "start": [ - 1, - 33 - ], - "name": "switch-statement.js", - "end": [ - 1, - 34 - ] - } - ] - }, - "summary": "Replaced '1' with '2'", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "switch-statement.js" - ], - "sha1": "fa74d55721267c11d2be5de262e9eb3100ba91f0", - "gitDir": "test/corpus/repos/javascript", - "sha2": "14d176ab7a67005a68ef8e96781993f1e9e8aff0" -} -,{ - "testCaseDescription": "javascript-switch-statement-delete-replacement-test", - "expectedResult": { - "changes": { - "switch-statement.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "switch-statement.js", - "end": [ - 1, - 48 - ] - } - }, - "summary": "Deleted the '2' switch statement", - "tag": "JSONSummary" - }, - { - "span": { - "this": { - "start": [ - 2, - 1 - ], - "name": "switch-statement.js", - "end": [ - 2, - 48 - ] - } - }, - "summary": "Deleted the '1' switch statement", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "switch-statement.js", - "end": [ - 2, - 48 - ] - } - }, - "summary": "Added the '2' switch statement", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "switch-statement.js" - ], - "sha1": "14d176ab7a67005a68ef8e96781993f1e9e8aff0", - "gitDir": "test/corpus/repos/javascript", - "sha2": "f3c50550c25a6a350e336bcb4acb19efaee5784b" -} -,{ - "testCaseDescription": "javascript-switch-statement-delete-test", - "expectedResult": { - "changes": { - "switch-statement.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "switch-statement.js", - "end": [ - 1, - 48 - ] - } - }, - "summary": "Deleted the '1' switch statement", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "switch-statement.js" - ], - "sha1": "f3c50550c25a6a350e336bcb4acb19efaee5784b", - "gitDir": "test/corpus/repos/javascript", - "sha2": "43e7f35abe631d346d4a6d0b20df2215a9844b2a" -} -,{ - "testCaseDescription": "javascript-switch-statement-delete-rest-test", - "expectedResult": { - "changes": { - "switch-statement.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "switch-statement.js", - "end": [ - 1, - 48 - ] - } - }, - "summary": "Deleted the '2' switch statement", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "switch-statement.js" - ], - "sha1": "43e7f35abe631d346d4a6d0b20df2215a9844b2a", - "gitDir": "test/corpus/repos/javascript", - "sha2": "ef9e2caec95767f4944840fd5db7f43806b65d4e" -}] diff --git a/test/corpus/diff-summaries/javascript/template-string.json b/test/corpus/diff-summaries/javascript/template-string.json deleted file mode 100644 index a1010f774..000000000 --- a/test/corpus/diff-summaries/javascript/template-string.json +++ /dev/null @@ -1,308 +0,0 @@ -[{ - "testCaseDescription": "javascript-template-string-insert-test", - "expectedResult": { - "changes": { - "template-string.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "template-string.js", - "end": [ - 1, - 11 - ] - } - }, - "summary": "Added the '`one line`' template string", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "template-string.js" - ], - "sha1": "125f2e2e8e65a10784e72bb113319c805d4f42ac", - "gitDir": "test/corpus/repos/javascript", - "sha2": "a3356557da2051db1550e86d98e0125c04a76786" -} -,{ - "testCaseDescription": "javascript-template-string-replacement-insert-test", - "expectedResult": { - "changes": { - "template-string.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "template-string.js", - "end": [ - 1, - 13 - ] - } - }, - "summary": "Added the '`multi line`' template string", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "template-string.js", - "end": [ - 2, - 11 - ] - } - }, - "summary": "Added the '`one line`' template string", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "template-string.js" - ], - "sha1": "a3356557da2051db1550e86d98e0125c04a76786", - "gitDir": "test/corpus/repos/javascript", - "sha2": "90c33afc22831d46016cae3ef48184f5181a3209" -} -,{ - "testCaseDescription": "javascript-template-string-delete-insert-test", - "expectedResult": { - "changes": { - "template-string.js": [ - { - "span": { - "these": [ - { - "start": [ - 1, - 1 - ], - "name": "template-string.js", - "end": [ - 1, - 13 - ] - }, - { - "start": [ - 1, - 1 - ], - "name": "template-string.js", - "end": [ - 1, - 11 - ] - } - ] - }, - "summary": "Replaced the '`multi line`' template string with the '`one line`' template string", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "template-string.js" - ], - "sha1": "90c33afc22831d46016cae3ef48184f5181a3209", - "gitDir": "test/corpus/repos/javascript", - "sha2": "41c65d10f9fd1e98f553137da5ac3ec04a6e816a" -} -,{ - "testCaseDescription": "javascript-template-string-replacement-test", - "expectedResult": { - "changes": { - "template-string.js": [ - { - "span": { - "these": [ - { - "start": [ - 1, - 1 - ], - "name": "template-string.js", - "end": [ - 1, - 11 - ] - }, - { - "start": [ - 1, - 1 - ], - "name": "template-string.js", - "end": [ - 1, - 13 - ] - } - ] - }, - "summary": "Replaced the '`one line`' template string with the '`multi line`' template string", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "template-string.js" - ], - "sha1": "41c65d10f9fd1e98f553137da5ac3ec04a6e816a", - "gitDir": "test/corpus/repos/javascript", - "sha2": "1f70c585f7fd042fbc6d4318040f4cf1346a8f6d" -} -,{ - "testCaseDescription": "javascript-template-string-delete-replacement-test", - "expectedResult": { - "changes": { - "template-string.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "template-string.js", - "end": [ - 1, - 13 - ] - } - }, - "summary": "Deleted the '`multi line`' template string", - "tag": "JSONSummary" - }, - { - "span": { - "this": { - "start": [ - 2, - 1 - ], - "name": "template-string.js", - "end": [ - 2, - 11 - ] - } - }, - "summary": "Deleted the '`one line`' template string", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "template-string.js", - "end": [ - 2, - 13 - ] - } - }, - "summary": "Added the '`multi line`' template string", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "template-string.js" - ], - "sha1": "1f70c585f7fd042fbc6d4318040f4cf1346a8f6d", - "gitDir": "test/corpus/repos/javascript", - "sha2": "53609feaa56d71f8929c26bf0653e4559ed8baa4" -} -,{ - "testCaseDescription": "javascript-template-string-delete-test", - "expectedResult": { - "changes": { - "template-string.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "template-string.js", - "end": [ - 1, - 11 - ] - } - }, - "summary": "Deleted the '`one line`' template string", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "template-string.js" - ], - "sha1": "53609feaa56d71f8929c26bf0653e4559ed8baa4", - "gitDir": "test/corpus/repos/javascript", - "sha2": "bc277e6624d14eb866c65fb7668dcd6a678b9eaa" -} -,{ - "testCaseDescription": "javascript-template-string-delete-rest-test", - "expectedResult": { - "changes": { - "template-string.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "template-string.js", - "end": [ - 1, - 13 - ] - } - }, - "summary": "Deleted the '`multi line`' template string", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "template-string.js" - ], - "sha1": "bc277e6624d14eb866c65fb7668dcd6a678b9eaa", - "gitDir": "test/corpus/repos/javascript", - "sha2": "2017d7a8b91c62e06d4de3654b0a7a2d550e55b9" -}] diff --git a/test/corpus/diff-summaries/javascript/ternary.json b/test/corpus/diff-summaries/javascript/ternary.json deleted file mode 100644 index 97efc7f09..000000000 --- a/test/corpus/diff-summaries/javascript/ternary.json +++ /dev/null @@ -1,316 +0,0 @@ -[{ - "testCaseDescription": "javascript-ternary-insert-test", - "expectedResult": { - "changes": { - "ternary.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "ternary.js", - "end": [ - 1, - 26 - ] - } - }, - "summary": "Added the 'condition' ternary expression", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "ternary.js" - ], - "sha1": "7d593b800284097a4d4f70fe25aebef1cbbe69c3", - "gitDir": "test/corpus/repos/javascript", - "sha2": "df07d4313d01aaa48070484b81a515d4b38e229b" -} -,{ - "testCaseDescription": "javascript-ternary-replacement-insert-test", - "expectedResult": { - "changes": { - "ternary.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "ternary.js", - "end": [ - 1, - 51 - ] - } - }, - "summary": "Added the 'x.y' assignment", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "ternary.js", - "end": [ - 2, - 26 - ] - } - }, - "summary": "Added the 'condition' ternary expression", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "ternary.js" - ], - "sha1": "df07d4313d01aaa48070484b81a515d4b38e229b", - "gitDir": "test/corpus/repos/javascript", - "sha2": "d816f96bfa4a4e3f7d2fed8a1873e45aba4793cb" -} -,{ - "testCaseDescription": "javascript-ternary-delete-insert-test", - "expectedResult": { - "changes": { - "ternary.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "ternary.js", - "end": [ - 1, - 26 - ] - } - }, - "summary": "Added the 'condition' ternary expression", - "tag": "JSONSummary" - }, - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "ternary.js", - "end": [ - 1, - 51 - ] - } - }, - "summary": "Deleted the 'x.y' assignment", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "ternary.js" - ], - "sha1": "d816f96bfa4a4e3f7d2fed8a1873e45aba4793cb", - "gitDir": "test/corpus/repos/javascript", - "sha2": "7a965762c520641e9bed35cf4f64a0d7aa2caf9d" -} -,{ - "testCaseDescription": "javascript-ternary-replacement-test", - "expectedResult": { - "changes": { - "ternary.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "ternary.js", - "end": [ - 1, - 51 - ] - } - }, - "summary": "Added the 'x.y' assignment", - "tag": "JSONSummary" - }, - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "ternary.js", - "end": [ - 1, - 26 - ] - } - }, - "summary": "Deleted the 'condition' ternary expression", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "ternary.js" - ], - "sha1": "7a965762c520641e9bed35cf4f64a0d7aa2caf9d", - "gitDir": "test/corpus/repos/javascript", - "sha2": "d5904189993b67d55a85720cfe76815ef2861496" -} -,{ - "testCaseDescription": "javascript-ternary-delete-replacement-test", - "expectedResult": { - "changes": { - "ternary.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "ternary.js", - "end": [ - 1, - 51 - ] - } - }, - "summary": "Deleted the 'x.y' assignment", - "tag": "JSONSummary" - }, - { - "span": { - "this": { - "start": [ - 2, - 1 - ], - "name": "ternary.js", - "end": [ - 2, - 26 - ] - } - }, - "summary": "Deleted the 'condition' ternary expression", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "ternary.js", - "end": [ - 2, - 51 - ] - } - }, - "summary": "Added the 'x.y' assignment", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "ternary.js" - ], - "sha1": "d5904189993b67d55a85720cfe76815ef2861496", - "gitDir": "test/corpus/repos/javascript", - "sha2": "e7d084239ead8cbe5eb51443a181c7d43f0458aa" -} -,{ - "testCaseDescription": "javascript-ternary-delete-test", - "expectedResult": { - "changes": { - "ternary.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "ternary.js", - "end": [ - 1, - 26 - ] - } - }, - "summary": "Deleted the 'condition' ternary expression", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "ternary.js" - ], - "sha1": "e7d084239ead8cbe5eb51443a181c7d43f0458aa", - "gitDir": "test/corpus/repos/javascript", - "sha2": "6feb3f80562f534aaef7a5c3814f69c8b509b487" -} -,{ - "testCaseDescription": "javascript-ternary-delete-rest-test", - "expectedResult": { - "changes": { - "ternary.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "ternary.js", - "end": [ - 1, - 51 - ] - } - }, - "summary": "Deleted the 'x.y' assignment", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "ternary.js" - ], - "sha1": "6feb3f80562f534aaef7a5c3814f69c8b509b487", - "gitDir": "test/corpus/repos/javascript", - "sha2": "10e446483f5cfbc3b6a595cf22bcd8e5b4b7fa1f" -}] diff --git a/test/corpus/diff-summaries/javascript/this-expression.json b/test/corpus/diff-summaries/javascript/this-expression.json deleted file mode 100644 index f26e86f5b..000000000 --- a/test/corpus/diff-summaries/javascript/this-expression.json +++ /dev/null @@ -1,316 +0,0 @@ -[{ - "testCaseDescription": "javascript-this-expression-insert-test", - "expectedResult": { - "changes": { - "this-expression.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "this-expression.js", - "end": [ - 1, - 5 - ] - } - }, - "summary": "Added the 'this' identifier", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "this-expression.js" - ], - "sha1": "ebab90bd29d724f6dda4d39a32a6fa7d0b9adf52", - "gitDir": "test/corpus/repos/javascript", - "sha2": "e28cc543f4228740ad7e5b4680afb8cbf9c51243" -} -,{ - "testCaseDescription": "javascript-this-expression-replacement-insert-test", - "expectedResult": { - "changes": { - "this-expression.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "this-expression.js", - "end": [ - 1, - 13 - ] - } - }, - "summary": "Added the 'this' return statement", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "this-expression.js", - "end": [ - 2, - 5 - ] - } - }, - "summary": "Added the 'this' identifier", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "this-expression.js" - ], - "sha1": "e28cc543f4228740ad7e5b4680afb8cbf9c51243", - "gitDir": "test/corpus/repos/javascript", - "sha2": "552578420a183fd55293708a7cc2b243ca1d657e" -} -,{ - "testCaseDescription": "javascript-this-expression-delete-insert-test", - "expectedResult": { - "changes": { - "this-expression.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "this-expression.js", - "end": [ - 1, - 5 - ] - } - }, - "summary": "Added the 'this' identifier", - "tag": "JSONSummary" - }, - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "this-expression.js", - "end": [ - 1, - 13 - ] - } - }, - "summary": "Deleted the 'this' return statement", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "this-expression.js" - ], - "sha1": "552578420a183fd55293708a7cc2b243ca1d657e", - "gitDir": "test/corpus/repos/javascript", - "sha2": "39b0ac559626f4dc67b1e083a93a785c50ba88f6" -} -,{ - "testCaseDescription": "javascript-this-expression-replacement-test", - "expectedResult": { - "changes": { - "this-expression.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "this-expression.js", - "end": [ - 1, - 13 - ] - } - }, - "summary": "Added the 'this' return statement", - "tag": "JSONSummary" - }, - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "this-expression.js", - "end": [ - 1, - 5 - ] - } - }, - "summary": "Deleted the 'this' identifier", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "this-expression.js" - ], - "sha1": "39b0ac559626f4dc67b1e083a93a785c50ba88f6", - "gitDir": "test/corpus/repos/javascript", - "sha2": "1792d3469977ef42255a501612f9ab858d918c65" -} -,{ - "testCaseDescription": "javascript-this-expression-delete-replacement-test", - "expectedResult": { - "changes": { - "this-expression.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "this-expression.js", - "end": [ - 1, - 13 - ] - } - }, - "summary": "Deleted the 'this' return statement", - "tag": "JSONSummary" - }, - { - "span": { - "this": { - "start": [ - 2, - 1 - ], - "name": "this-expression.js", - "end": [ - 2, - 5 - ] - } - }, - "summary": "Deleted the 'this' identifier", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "this-expression.js", - "end": [ - 2, - 13 - ] - } - }, - "summary": "Added the 'this' return statement", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "this-expression.js" - ], - "sha1": "1792d3469977ef42255a501612f9ab858d918c65", - "gitDir": "test/corpus/repos/javascript", - "sha2": "1153598d3f6368a7cada09f10d73306a6e6857a3" -} -,{ - "testCaseDescription": "javascript-this-expression-delete-test", - "expectedResult": { - "changes": { - "this-expression.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "this-expression.js", - "end": [ - 1, - 5 - ] - } - }, - "summary": "Deleted the 'this' identifier", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "this-expression.js" - ], - "sha1": "1153598d3f6368a7cada09f10d73306a6e6857a3", - "gitDir": "test/corpus/repos/javascript", - "sha2": "d2ae1e6938e47ab5b41d0eb89fb0cd1087445e06" -} -,{ - "testCaseDescription": "javascript-this-expression-delete-rest-test", - "expectedResult": { - "changes": { - "this-expression.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "this-expression.js", - "end": [ - 1, - 13 - ] - } - }, - "summary": "Deleted the 'this' return statement", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "this-expression.js" - ], - "sha1": "d2ae1e6938e47ab5b41d0eb89fb0cd1087445e06", - "gitDir": "test/corpus/repos/javascript", - "sha2": "11a27a81f8e7e33aac2eb0844d3465acf8f9bb0d" -}] diff --git a/test/corpus/diff-summaries/javascript/throw-statement.json b/test/corpus/diff-summaries/javascript/throw-statement.json deleted file mode 100644 index 7dcc88d6d..000000000 --- a/test/corpus/diff-summaries/javascript/throw-statement.json +++ /dev/null @@ -1,308 +0,0 @@ -[{ - "testCaseDescription": "javascript-throw-statement-insert-test", - "expectedResult": { - "changes": { - "throw-statement.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "throw-statement.js", - "end": [ - 1, - 26 - ] - } - }, - "summary": "Added the 'new Error(\"uh oh\")' throw statement", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "throw-statement.js" - ], - "sha1": "ef9e2caec95767f4944840fd5db7f43806b65d4e", - "gitDir": "test/corpus/repos/javascript", - "sha2": "e8ffd161fc105086e8c085de252fd15f1582df33" -} -,{ - "testCaseDescription": "javascript-throw-statement-replacement-insert-test", - "expectedResult": { - "changes": { - "throw-statement.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "throw-statement.js", - "end": [ - 1, - 29 - ] - } - }, - "summary": "Added the 'new Error(\"oooooops\")' throw statement", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "throw-statement.js", - "end": [ - 2, - 26 - ] - } - }, - "summary": "Added the 'new Error(\"uh oh\")' throw statement", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "throw-statement.js" - ], - "sha1": "e8ffd161fc105086e8c085de252fd15f1582df33", - "gitDir": "test/corpus/repos/javascript", - "sha2": "0ff2edba17e3040f87a6685ed6ea554a4f520254" -} -,{ - "testCaseDescription": "javascript-throw-statement-delete-insert-test", - "expectedResult": { - "changes": { - "throw-statement.js": [ - { - "span": { - "these": [ - { - "start": [ - 1, - 17 - ], - "name": "throw-statement.js", - "end": [ - 1, - 27 - ] - }, - { - "start": [ - 1, - 17 - ], - "name": "throw-statement.js", - "end": [ - 1, - 24 - ] - } - ] - }, - "summary": "Replaced the \"oooooops\" string with the \"uh oh\" string in the Error(\"uh oh\") function call", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "throw-statement.js" - ], - "sha1": "0ff2edba17e3040f87a6685ed6ea554a4f520254", - "gitDir": "test/corpus/repos/javascript", - "sha2": "911f32d28e0aa19e34646b9917cdcf6eb51b16f0" -} -,{ - "testCaseDescription": "javascript-throw-statement-replacement-test", - "expectedResult": { - "changes": { - "throw-statement.js": [ - { - "span": { - "these": [ - { - "start": [ - 1, - 17 - ], - "name": "throw-statement.js", - "end": [ - 1, - 24 - ] - }, - { - "start": [ - 1, - 17 - ], - "name": "throw-statement.js", - "end": [ - 1, - 27 - ] - } - ] - }, - "summary": "Replaced the \"uh oh\" string with the \"oooooops\" string in the Error(\"oooooops\") function call", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "throw-statement.js" - ], - "sha1": "911f32d28e0aa19e34646b9917cdcf6eb51b16f0", - "gitDir": "test/corpus/repos/javascript", - "sha2": "441deaae5ebff81f6802d5e2f9f4ae276db41c3b" -} -,{ - "testCaseDescription": "javascript-throw-statement-delete-replacement-test", - "expectedResult": { - "changes": { - "throw-statement.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "throw-statement.js", - "end": [ - 1, - 29 - ] - } - }, - "summary": "Deleted the 'new Error(\"oooooops\")' throw statement", - "tag": "JSONSummary" - }, - { - "span": { - "this": { - "start": [ - 2, - 1 - ], - "name": "throw-statement.js", - "end": [ - 2, - 26 - ] - } - }, - "summary": "Deleted the 'new Error(\"uh oh\")' throw statement", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "throw-statement.js", - "end": [ - 2, - 29 - ] - } - }, - "summary": "Added the 'new Error(\"oooooops\")' throw statement", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "throw-statement.js" - ], - "sha1": "441deaae5ebff81f6802d5e2f9f4ae276db41c3b", - "gitDir": "test/corpus/repos/javascript", - "sha2": "753074bc4ed4fbcc549b57307a13bc068a4dc0ff" -} -,{ - "testCaseDescription": "javascript-throw-statement-delete-test", - "expectedResult": { - "changes": { - "throw-statement.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "throw-statement.js", - "end": [ - 1, - 26 - ] - } - }, - "summary": "Deleted the 'new Error(\"uh oh\")' throw statement", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "throw-statement.js" - ], - "sha1": "753074bc4ed4fbcc549b57307a13bc068a4dc0ff", - "gitDir": "test/corpus/repos/javascript", - "sha2": "41cdf55b68dce5bdc74df0f541995f9603d2014d" -} -,{ - "testCaseDescription": "javascript-throw-statement-delete-rest-test", - "expectedResult": { - "changes": { - "throw-statement.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "throw-statement.js", - "end": [ - 1, - 29 - ] - } - }, - "summary": "Deleted the 'new Error(\"oooooops\")' throw statement", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "throw-statement.js" - ], - "sha1": "41cdf55b68dce5bdc74df0f541995f9603d2014d", - "gitDir": "test/corpus/repos/javascript", - "sha2": "8853e12eb348f42061f28c7a65748dd8c2b6cdda" -}] diff --git a/test/corpus/diff-summaries/javascript/true.json b/test/corpus/diff-summaries/javascript/true.json deleted file mode 100644 index 4a82be170..000000000 --- a/test/corpus/diff-summaries/javascript/true.json +++ /dev/null @@ -1,316 +0,0 @@ -[{ - "testCaseDescription": "javascript-true-insert-test", - "expectedResult": { - "changes": { - "true.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "true.js", - "end": [ - 1, - 5 - ] - } - }, - "summary": "Added 'true'", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "true.js" - ], - "sha1": "c40f78d8ec9a8873d55c8d368978e674c1dfc2d8", - "gitDir": "test/corpus/repos/javascript", - "sha2": "656b27635a5debd119ebc672643c188946ff6963" -} -,{ - "testCaseDescription": "javascript-true-replacement-insert-test", - "expectedResult": { - "changes": { - "true.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "true.js", - "end": [ - 1, - 13 - ] - } - }, - "summary": "Added the 'true' return statement", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "true.js", - "end": [ - 2, - 5 - ] - } - }, - "summary": "Added 'true'", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "true.js" - ], - "sha1": "656b27635a5debd119ebc672643c188946ff6963", - "gitDir": "test/corpus/repos/javascript", - "sha2": "63973077f6a477896c7a929a14079bf4bbaadb30" -} -,{ - "testCaseDescription": "javascript-true-delete-insert-test", - "expectedResult": { - "changes": { - "true.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "true.js", - "end": [ - 1, - 5 - ] - } - }, - "summary": "Added 'true'", - "tag": "JSONSummary" - }, - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "true.js", - "end": [ - 1, - 13 - ] - } - }, - "summary": "Deleted the 'true' return statement", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "true.js" - ], - "sha1": "63973077f6a477896c7a929a14079bf4bbaadb30", - "gitDir": "test/corpus/repos/javascript", - "sha2": "3853f8cb4f7f378206fafa6409d03a2630a15f1a" -} -,{ - "testCaseDescription": "javascript-true-replacement-test", - "expectedResult": { - "changes": { - "true.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "true.js", - "end": [ - 1, - 13 - ] - } - }, - "summary": "Added the 'true' return statement", - "tag": "JSONSummary" - }, - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "true.js", - "end": [ - 1, - 5 - ] - } - }, - "summary": "Deleted 'true'", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "true.js" - ], - "sha1": "3853f8cb4f7f378206fafa6409d03a2630a15f1a", - "gitDir": "test/corpus/repos/javascript", - "sha2": "e19548511ad78553ec47f28afe71c1b05d3cefb0" -} -,{ - "testCaseDescription": "javascript-true-delete-replacement-test", - "expectedResult": { - "changes": { - "true.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "true.js", - "end": [ - 1, - 13 - ] - } - }, - "summary": "Deleted the 'true' return statement", - "tag": "JSONSummary" - }, - { - "span": { - "this": { - "start": [ - 2, - 1 - ], - "name": "true.js", - "end": [ - 2, - 5 - ] - } - }, - "summary": "Deleted 'true'", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "true.js", - "end": [ - 2, - 13 - ] - } - }, - "summary": "Added the 'true' return statement", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "true.js" - ], - "sha1": "e19548511ad78553ec47f28afe71c1b05d3cefb0", - "gitDir": "test/corpus/repos/javascript", - "sha2": "551e03fb9cd6912f8f1fa0672eaa64c3c6568bd9" -} -,{ - "testCaseDescription": "javascript-true-delete-test", - "expectedResult": { - "changes": { - "true.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "true.js", - "end": [ - 1, - 5 - ] - } - }, - "summary": "Deleted 'true'", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "true.js" - ], - "sha1": "551e03fb9cd6912f8f1fa0672eaa64c3c6568bd9", - "gitDir": "test/corpus/repos/javascript", - "sha2": "77cbe0371de746912cba103518368ac85987da73" -} -,{ - "testCaseDescription": "javascript-true-delete-rest-test", - "expectedResult": { - "changes": { - "true.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "true.js", - "end": [ - 1, - 13 - ] - } - }, - "summary": "Deleted the 'true' return statement", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "true.js" - ], - "sha1": "77cbe0371de746912cba103518368ac85987da73", - "gitDir": "test/corpus/repos/javascript", - "sha2": "d1241fa4218f33189f78a91a9513ca7e2120a2a0" -}] diff --git a/test/corpus/diff-summaries/javascript/try-statement.json b/test/corpus/diff-summaries/javascript/try-statement.json deleted file mode 100644 index b8ce833ea..000000000 --- a/test/corpus/diff-summaries/javascript/try-statement.json +++ /dev/null @@ -1,368 +0,0 @@ -[{ - "testCaseDescription": "javascript-try-statement-insert-test", - "expectedResult": { - "changes": { - "try-statement.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "try-statement.js", - "end": [ - 1, - 39 - ] - } - }, - "summary": "Added the '{ f; }' try statement", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "try-statement.js" - ], - "sha1": "8853e12eb348f42061f28c7a65748dd8c2b6cdda", - "gitDir": "test/corpus/repos/javascript", - "sha2": "9a940b48df9acd8141dce91926326bb545a35ce9" -} -,{ - "testCaseDescription": "javascript-try-statement-replacement-insert-test", - "expectedResult": { - "changes": { - "try-statement.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "try-statement.js", - "end": [ - 1, - 39 - ] - } - }, - "summary": "Added the '{ f; }' try statement", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "try-statement.js", - "end": [ - 2, - 39 - ] - } - }, - "summary": "Added the '{ f; }' try statement", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "try-statement.js" - ], - "sha1": "9a940b48df9acd8141dce91926326bb545a35ce9", - "gitDir": "test/corpus/repos/javascript", - "sha2": "14485b720f542fc02c659aeb388d28a4f23d5eca" -} -,{ - "testCaseDescription": "javascript-try-statement-delete-insert-test", - "expectedResult": { - "changes": { - "try-statement.js": [ - { - "span": { - "these": [ - { - "start": [ - 1, - 20 - ], - "name": "try-statement.js", - "end": [ - 1, - 21 - ] - }, - { - "start": [ - 1, - 20 - ], - "name": "try-statement.js", - "end": [ - 1, - 21 - ] - } - ] - }, - "summary": "Replaced the 'h' identifier with the 'g' identifier", - "tag": "JSONSummary" - }, - { - "span": { - "these": [ - { - "start": [ - 1, - 35 - ], - "name": "try-statement.js", - "end": [ - 1, - 36 - ] - }, - { - "start": [ - 1, - 35 - ], - "name": "try-statement.js", - "end": [ - 1, - 36 - ] - } - ] - }, - "summary": "Replaced the 'g' identifier with the 'h' identifier", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "try-statement.js" - ], - "sha1": "14485b720f542fc02c659aeb388d28a4f23d5eca", - "gitDir": "test/corpus/repos/javascript", - "sha2": "937bc39ba6b5a8ea39d5e70a05aca172340b34b8" -} -,{ - "testCaseDescription": "javascript-try-statement-replacement-test", - "expectedResult": { - "changes": { - "try-statement.js": [ - { - "span": { - "these": [ - { - "start": [ - 1, - 20 - ], - "name": "try-statement.js", - "end": [ - 1, - 21 - ] - }, - { - "start": [ - 1, - 20 - ], - "name": "try-statement.js", - "end": [ - 1, - 21 - ] - } - ] - }, - "summary": "Replaced the 'g' identifier with the 'h' identifier", - "tag": "JSONSummary" - }, - { - "span": { - "these": [ - { - "start": [ - 1, - 35 - ], - "name": "try-statement.js", - "end": [ - 1, - 36 - ] - }, - { - "start": [ - 1, - 35 - ], - "name": "try-statement.js", - "end": [ - 1, - 36 - ] - } - ] - }, - "summary": "Replaced the 'h' identifier with the 'g' identifier", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "try-statement.js" - ], - "sha1": "937bc39ba6b5a8ea39d5e70a05aca172340b34b8", - "gitDir": "test/corpus/repos/javascript", - "sha2": "d5388b993d81d166c72a2c0851cadf209a53e663" -} -,{ - "testCaseDescription": "javascript-try-statement-delete-replacement-test", - "expectedResult": { - "changes": { - "try-statement.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "try-statement.js", - "end": [ - 1, - 39 - ] - } - }, - "summary": "Deleted the '{ f; }' try statement", - "tag": "JSONSummary" - }, - { - "span": { - "this": { - "start": [ - 2, - 1 - ], - "name": "try-statement.js", - "end": [ - 2, - 39 - ] - } - }, - "summary": "Deleted the '{ f; }' try statement", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "try-statement.js", - "end": [ - 2, - 39 - ] - } - }, - "summary": "Added the '{ f; }' try statement", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "try-statement.js" - ], - "sha1": "d5388b993d81d166c72a2c0851cadf209a53e663", - "gitDir": "test/corpus/repos/javascript", - "sha2": "dcc5fa3d3acd27cfef2eab524cd619a2518e375f" -} -,{ - "testCaseDescription": "javascript-try-statement-delete-test", - "expectedResult": { - "changes": { - "try-statement.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "try-statement.js", - "end": [ - 1, - 39 - ] - } - }, - "summary": "Deleted the '{ f; }' try statement", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "try-statement.js" - ], - "sha1": "dcc5fa3d3acd27cfef2eab524cd619a2518e375f", - "gitDir": "test/corpus/repos/javascript", - "sha2": "4f2e99ffade0f4b59764c6dc000ea251ffd1876b" -} -,{ - "testCaseDescription": "javascript-try-statement-delete-rest-test", - "expectedResult": { - "changes": { - "try-statement.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "try-statement.js", - "end": [ - 1, - 39 - ] - } - }, - "summary": "Deleted the '{ f; }' try statement", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "try-statement.js" - ], - "sha1": "4f2e99ffade0f4b59764c6dc000ea251ffd1876b", - "gitDir": "test/corpus/repos/javascript", - "sha2": "87a75eabc61b58f15583babf507419181ab63aeb" -}] diff --git a/test/corpus/diff-summaries/javascript/type-operator.json b/test/corpus/diff-summaries/javascript/type-operator.json deleted file mode 100644 index 33fe2faf5..000000000 --- a/test/corpus/diff-summaries/javascript/type-operator.json +++ /dev/null @@ -1,282 +0,0 @@ -[{ - "testCaseDescription": "javascript-type-operator-insert-test", - "expectedResult": { - "changes": { - "type-operator.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "type-operator.js", - "end": [ - 1, - 9 - ] - } - }, - "summary": "Added the 'typeof x' operator", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "type-operator.js" - ], - "sha1": "10e446483f5cfbc3b6a595cf22bcd8e5b4b7fa1f", - "gitDir": "test/corpus/repos/javascript", - "sha2": "e824baf85c2455f92ee90fc9344ac39d72a50a14" -} -,{ - "testCaseDescription": "javascript-type-operator-replacement-insert-test", - "expectedResult": { - "changes": { - "type-operator.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "type-operator.js", - "end": [ - 1, - 20 - ] - } - }, - "summary": "Added the 'x instanceof String' operator", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "type-operator.js", - "end": [ - 2, - 9 - ] - } - }, - "summary": "Added the 'typeof x' operator", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "type-operator.js" - ], - "sha1": "e824baf85c2455f92ee90fc9344ac39d72a50a14", - "gitDir": "test/corpus/repos/javascript", - "sha2": "4c4620dc49de1618fc2688d086a90b0c33b56172" -} -,{ - "testCaseDescription": "javascript-type-operator-delete-insert-test", - "expectedResult": { - "changes": { - "type-operator.js": [ - { - "span": { - "this": { - "start": [ - 1, - 14 - ], - "name": "type-operator.js", - "end": [ - 1, - 20 - ] - } - }, - "summary": "Deleted the 'String' identifier", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "type-operator.js" - ], - "sha1": "4c4620dc49de1618fc2688d086a90b0c33b56172", - "gitDir": "test/corpus/repos/javascript", - "sha2": "cb84bfa2a54e105154cc4f64f3edbdec593da924" -} -,{ - "testCaseDescription": "javascript-type-operator-replacement-test", - "expectedResult": { - "changes": { - "type-operator.js": [ - { - "span": { - "that": { - "start": [ - 1, - 14 - ], - "name": "type-operator.js", - "end": [ - 1, - 20 - ] - } - }, - "summary": "Added the 'String' identifier", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "type-operator.js" - ], - "sha1": "cb84bfa2a54e105154cc4f64f3edbdec593da924", - "gitDir": "test/corpus/repos/javascript", - "sha2": "3906b75677e7e34461038b42a7d0eed388638d1a" -} -,{ - "testCaseDescription": "javascript-type-operator-delete-replacement-test", - "expectedResult": { - "changes": { - "type-operator.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "type-operator.js", - "end": [ - 1, - 20 - ] - } - }, - "summary": "Deleted the 'x instanceof String' operator", - "tag": "JSONSummary" - }, - { - "span": { - "this": { - "start": [ - 2, - 1 - ], - "name": "type-operator.js", - "end": [ - 2, - 9 - ] - } - }, - "summary": "Deleted the 'typeof x' operator", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "type-operator.js", - "end": [ - 2, - 20 - ] - } - }, - "summary": "Added the 'x instanceof String' operator", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "type-operator.js" - ], - "sha1": "3906b75677e7e34461038b42a7d0eed388638d1a", - "gitDir": "test/corpus/repos/javascript", - "sha2": "63321c3a8e510775ad5270c30d3f34d4c513363e" -} -,{ - "testCaseDescription": "javascript-type-operator-delete-test", - "expectedResult": { - "changes": { - "type-operator.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "type-operator.js", - "end": [ - 1, - 9 - ] - } - }, - "summary": "Deleted the 'typeof x' operator", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "type-operator.js" - ], - "sha1": "63321c3a8e510775ad5270c30d3f34d4c513363e", - "gitDir": "test/corpus/repos/javascript", - "sha2": "553f6f8d42f3dbd74e01e1e8eb376f10010728c5" -} -,{ - "testCaseDescription": "javascript-type-operator-delete-rest-test", - "expectedResult": { - "changes": { - "type-operator.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "type-operator.js", - "end": [ - 1, - 20 - ] - } - }, - "summary": "Deleted the 'x instanceof String' operator", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "type-operator.js" - ], - "sha1": "553f6f8d42f3dbd74e01e1e8eb376f10010728c5", - "gitDir": "test/corpus/repos/javascript", - "sha2": "0014c5d8fc3e6f9d08e268ebbb2d42919d5b4991" -}] diff --git a/test/corpus/diff-summaries/javascript/undefined.json b/test/corpus/diff-summaries/javascript/undefined.json deleted file mode 100644 index 3000186bf..000000000 --- a/test/corpus/diff-summaries/javascript/undefined.json +++ /dev/null @@ -1,316 +0,0 @@ -[{ - "testCaseDescription": "javascript-undefined-insert-test", - "expectedResult": { - "changes": { - "undefined.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "undefined.js", - "end": [ - 1, - 10 - ] - } - }, - "summary": "Added the 'undefined' identifier", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "undefined.js" - ], - "sha1": "43fd131de0f55fa1826e3fa3b95b88b7ba74fd68", - "gitDir": "test/corpus/repos/javascript", - "sha2": "a733439e831bb4ec5f6387c6ff60a2077a1e487d" -} -,{ - "testCaseDescription": "javascript-undefined-replacement-insert-test", - "expectedResult": { - "changes": { - "undefined.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "undefined.js", - "end": [ - 1, - 18 - ] - } - }, - "summary": "Added the 'undefined' return statement", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "undefined.js", - "end": [ - 2, - 10 - ] - } - }, - "summary": "Added the 'undefined' identifier", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "undefined.js" - ], - "sha1": "a733439e831bb4ec5f6387c6ff60a2077a1e487d", - "gitDir": "test/corpus/repos/javascript", - "sha2": "9e8bf000f2763e38b7d070a67c4162528edcebcb" -} -,{ - "testCaseDescription": "javascript-undefined-delete-insert-test", - "expectedResult": { - "changes": { - "undefined.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "undefined.js", - "end": [ - 1, - 10 - ] - } - }, - "summary": "Added the 'undefined' identifier", - "tag": "JSONSummary" - }, - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "undefined.js", - "end": [ - 1, - 18 - ] - } - }, - "summary": "Deleted the 'undefined' return statement", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "undefined.js" - ], - "sha1": "9e8bf000f2763e38b7d070a67c4162528edcebcb", - "gitDir": "test/corpus/repos/javascript", - "sha2": "f5de1863a90afffbf383144a36564fca6c7702ca" -} -,{ - "testCaseDescription": "javascript-undefined-replacement-test", - "expectedResult": { - "changes": { - "undefined.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "undefined.js", - "end": [ - 1, - 18 - ] - } - }, - "summary": "Added the 'undefined' return statement", - "tag": "JSONSummary" - }, - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "undefined.js", - "end": [ - 1, - 10 - ] - } - }, - "summary": "Deleted the 'undefined' identifier", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "undefined.js" - ], - "sha1": "f5de1863a90afffbf383144a36564fca6c7702ca", - "gitDir": "test/corpus/repos/javascript", - "sha2": "6f6fe3b3395ecaf60ae2e3b9d63f89c332770002" -} -,{ - "testCaseDescription": "javascript-undefined-delete-replacement-test", - "expectedResult": { - "changes": { - "undefined.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "undefined.js", - "end": [ - 1, - 18 - ] - } - }, - "summary": "Deleted the 'undefined' return statement", - "tag": "JSONSummary" - }, - { - "span": { - "this": { - "start": [ - 2, - 1 - ], - "name": "undefined.js", - "end": [ - 2, - 10 - ] - } - }, - "summary": "Deleted the 'undefined' identifier", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "undefined.js", - "end": [ - 2, - 18 - ] - } - }, - "summary": "Added the 'undefined' return statement", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "undefined.js" - ], - "sha1": "6f6fe3b3395ecaf60ae2e3b9d63f89c332770002", - "gitDir": "test/corpus/repos/javascript", - "sha2": "7c4790c8d32dd788ebf2c2857d39e88250608ea1" -} -,{ - "testCaseDescription": "javascript-undefined-delete-test", - "expectedResult": { - "changes": { - "undefined.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "undefined.js", - "end": [ - 1, - 10 - ] - } - }, - "summary": "Deleted the 'undefined' identifier", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "undefined.js" - ], - "sha1": "7c4790c8d32dd788ebf2c2857d39e88250608ea1", - "gitDir": "test/corpus/repos/javascript", - "sha2": "d802c686cf2a1012e7a239acdef816a7eb6b91ae" -} -,{ - "testCaseDescription": "javascript-undefined-delete-rest-test", - "expectedResult": { - "changes": { - "undefined.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "undefined.js", - "end": [ - 1, - 18 - ] - } - }, - "summary": "Deleted the 'undefined' return statement", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "undefined.js" - ], - "sha1": "d802c686cf2a1012e7a239acdef816a7eb6b91ae", - "gitDir": "test/corpus/repos/javascript", - "sha2": "c40f78d8ec9a8873d55c8d368978e674c1dfc2d8" -}] diff --git a/test/corpus/diff-summaries/javascript/var-declaration.json b/test/corpus/diff-summaries/javascript/var-declaration.json deleted file mode 100644 index e3fcde80b..000000000 --- a/test/corpus/diff-summaries/javascript/var-declaration.json +++ /dev/null @@ -1,512 +0,0 @@ -[{ - "testCaseDescription": "javascript-var-declaration-insert-test", - "expectedResult": { - "changes": { - "var-declaration.js": [ - { - "span": { - "that": { - "start": [ - 1, - 5 - ], - "name": "var-declaration.js", - "end": [ - 1, - 10 - ] - } - }, - "summary": "Added the 'x' variable", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "var-declaration.js" - ], - "sha1": "a5fb0a1bf511cc98cae35a20ea3a6dad064448bc", - "gitDir": "test/corpus/repos/javascript", - "sha2": "05bb0ae04ba1c8492dbc8091c77e84e7b8fa3706" -} -,{ - "testCaseDescription": "javascript-var-declaration-replacement-insert-test", - "expectedResult": { - "changes": { - "var-declaration.js": [ - { - "span": { - "that": { - "start": [ - 1, - 5 - ], - "name": "var-declaration.js", - "end": [ - 1, - 6 - ] - } - }, - "summary": "Added the 'x' variable", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 1, - 8 - ], - "name": "var-declaration.js", - "end": [ - 1, - 14 - ] - } - }, - "summary": "Added the 'y' variable", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 1, - 16 - ], - "name": "var-declaration.js", - "end": [ - 1, - 17 - ] - } - }, - "summary": "Added the 'z' variable", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 5 - ], - "name": "var-declaration.js", - "end": [ - 2, - 10 - ] - } - }, - "summary": "Added the 'x' variable", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "var-declaration.js" - ], - "sha1": "05bb0ae04ba1c8492dbc8091c77e84e7b8fa3706", - "gitDir": "test/corpus/repos/javascript", - "sha2": "390295f402454b7a8a89876ac729014f4c73f6cd" -} -,{ - "testCaseDescription": "javascript-var-declaration-delete-insert-test", - "expectedResult": { - "changes": { - "var-declaration.js": [ - { - "span": { - "these": [ - { - "start": [ - 1, - 5 - ], - "name": "var-declaration.js", - "end": [ - 1, - 6 - ] - }, - { - "start": [ - 1, - 5 - ], - "name": "var-declaration.js", - "end": [ - 1, - 10 - ] - } - ] - }, - "summary": "Replaced the 'x' variable with the 'x' variable", - "tag": "JSONSummary" - }, - { - "span": { - "this": { - "start": [ - 1, - 8 - ], - "name": "var-declaration.js", - "end": [ - 1, - 14 - ] - } - }, - "summary": "Deleted the 'y' variable", - "tag": "JSONSummary" - }, - { - "span": { - "this": { - "start": [ - 1, - 16 - ], - "name": "var-declaration.js", - "end": [ - 1, - 17 - ] - } - }, - "summary": "Deleted the 'z' variable", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "var-declaration.js" - ], - "sha1": "390295f402454b7a8a89876ac729014f4c73f6cd", - "gitDir": "test/corpus/repos/javascript", - "sha2": "ee63d737082c6fcdb3e782d9005591482b25c755" -} -,{ - "testCaseDescription": "javascript-var-declaration-replacement-test", - "expectedResult": { - "changes": { - "var-declaration.js": [ - { - "span": { - "these": [ - { - "start": [ - 1, - 5 - ], - "name": "var-declaration.js", - "end": [ - 1, - 10 - ] - }, - { - "start": [ - 1, - 5 - ], - "name": "var-declaration.js", - "end": [ - 1, - 6 - ] - } - ] - }, - "summary": "Replaced the 'x' variable with the 'x' variable", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 1, - 8 - ], - "name": "var-declaration.js", - "end": [ - 1, - 14 - ] - } - }, - "summary": "Added the 'y' variable", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 1, - 16 - ], - "name": "var-declaration.js", - "end": [ - 1, - 17 - ] - } - }, - "summary": "Added the 'z' variable", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "var-declaration.js" - ], - "sha1": "ee63d737082c6fcdb3e782d9005591482b25c755", - "gitDir": "test/corpus/repos/javascript", - "sha2": "14ab5aa6580823b08cde9a0d91e674bf712c4896" -} -,{ - "testCaseDescription": "javascript-var-declaration-delete-replacement-test", - "expectedResult": { - "changes": { - "var-declaration.js": [ - { - "span": { - "this": { - "start": [ - 1, - 5 - ], - "name": "var-declaration.js", - "end": [ - 1, - 6 - ] - } - }, - "summary": "Deleted the 'x' variable", - "tag": "JSONSummary" - }, - { - "span": { - "this": { - "start": [ - 1, - 8 - ], - "name": "var-declaration.js", - "end": [ - 1, - 14 - ] - } - }, - "summary": "Deleted the 'y' variable", - "tag": "JSONSummary" - }, - { - "span": { - "this": { - "start": [ - 1, - 16 - ], - "name": "var-declaration.js", - "end": [ - 1, - 17 - ] - } - }, - "summary": "Deleted the 'z' variable", - "tag": "JSONSummary" - }, - { - "span": { - "this": { - "start": [ - 2, - 5 - ], - "name": "var-declaration.js", - "end": [ - 2, - 10 - ] - } - }, - "summary": "Deleted the 'x' variable", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 5 - ], - "name": "var-declaration.js", - "end": [ - 2, - 6 - ] - } - }, - "summary": "Added the 'x' variable", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 8 - ], - "name": "var-declaration.js", - "end": [ - 2, - 14 - ] - } - }, - "summary": "Added the 'y' variable", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 16 - ], - "name": "var-declaration.js", - "end": [ - 2, - 17 - ] - } - }, - "summary": "Added the 'z' variable", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "var-declaration.js" - ], - "sha1": "14ab5aa6580823b08cde9a0d91e674bf712c4896", - "gitDir": "test/corpus/repos/javascript", - "sha2": "4949f1ef2caaf01fc368e0fb8010a90a05550c92" -} -,{ - "testCaseDescription": "javascript-var-declaration-delete-test", - "expectedResult": { - "changes": { - "var-declaration.js": [ - { - "span": { - "this": { - "start": [ - 1, - 5 - ], - "name": "var-declaration.js", - "end": [ - 1, - 10 - ] - } - }, - "summary": "Deleted the 'x' variable", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "var-declaration.js" - ], - "sha1": "4949f1ef2caaf01fc368e0fb8010a90a05550c92", - "gitDir": "test/corpus/repos/javascript", - "sha2": "bedd174ec888f89deff0be9e6cd87ecf1404c2d5" -} -,{ - "testCaseDescription": "javascript-var-declaration-delete-rest-test", - "expectedResult": { - "changes": { - "var-declaration.js": [ - { - "span": { - "this": { - "start": [ - 1, - 5 - ], - "name": "var-declaration.js", - "end": [ - 1, - 6 - ] - } - }, - "summary": "Deleted the 'x' variable", - "tag": "JSONSummary" - }, - { - "span": { - "this": { - "start": [ - 1, - 8 - ], - "name": "var-declaration.js", - "end": [ - 1, - 14 - ] - } - }, - "summary": "Deleted the 'y' variable", - "tag": "JSONSummary" - }, - { - "span": { - "this": { - "start": [ - 1, - 16 - ], - "name": "var-declaration.js", - "end": [ - 1, - 17 - ] - } - }, - "summary": "Deleted the 'z' variable", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "var-declaration.js" - ], - "sha1": "bedd174ec888f89deff0be9e6cd87ecf1404c2d5", - "gitDir": "test/corpus/repos/javascript", - "sha2": "b00fa825ca435ba80830373e95ab22dd77ce9326" -}] diff --git a/test/corpus/diff-summaries/javascript/variable.json b/test/corpus/diff-summaries/javascript/variable.json deleted file mode 100644 index 19f521a62..000000000 --- a/test/corpus/diff-summaries/javascript/variable.json +++ /dev/null @@ -1,308 +0,0 @@ -[{ - "testCaseDescription": "javascript-variable-insert-test", - "expectedResult": { - "changes": { - "variable.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "variable.js", - "end": [ - 1, - 7 - ] - } - }, - "summary": "Added the 'theVar' identifier", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "variable.js" - ], - "sha1": "7cd0762fb1e84cad3dcf9a1c41b07c8112c888fd", - "gitDir": "test/corpus/repos/javascript", - "sha2": "d997c1093fa0c616e4a65bdb9d406275cdd5802d" -} -,{ - "testCaseDescription": "javascript-variable-replacement-insert-test", - "expectedResult": { - "changes": { - "variable.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "variable.js", - "end": [ - 1, - 8 - ] - } - }, - "summary": "Added the 'theVar2' identifier", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "variable.js", - "end": [ - 2, - 7 - ] - } - }, - "summary": "Added the 'theVar' identifier", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "variable.js" - ], - "sha1": "d997c1093fa0c616e4a65bdb9d406275cdd5802d", - "gitDir": "test/corpus/repos/javascript", - "sha2": "d53db14bcba93489810bcd1ac51b4b15306a1ae6" -} -,{ - "testCaseDescription": "javascript-variable-delete-insert-test", - "expectedResult": { - "changes": { - "variable.js": [ - { - "span": { - "these": [ - { - "start": [ - 1, - 1 - ], - "name": "variable.js", - "end": [ - 1, - 8 - ] - }, - { - "start": [ - 1, - 1 - ], - "name": "variable.js", - "end": [ - 1, - 7 - ] - } - ] - }, - "summary": "Replaced the 'theVar2' identifier with the 'theVar' identifier", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "variable.js" - ], - "sha1": "d53db14bcba93489810bcd1ac51b4b15306a1ae6", - "gitDir": "test/corpus/repos/javascript", - "sha2": "3e07fecc10461c1d47c18a19bea04d61a0dfc83a" -} -,{ - "testCaseDescription": "javascript-variable-replacement-test", - "expectedResult": { - "changes": { - "variable.js": [ - { - "span": { - "these": [ - { - "start": [ - 1, - 1 - ], - "name": "variable.js", - "end": [ - 1, - 7 - ] - }, - { - "start": [ - 1, - 1 - ], - "name": "variable.js", - "end": [ - 1, - 8 - ] - } - ] - }, - "summary": "Replaced the 'theVar' identifier with the 'theVar2' identifier", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "variable.js" - ], - "sha1": "3e07fecc10461c1d47c18a19bea04d61a0dfc83a", - "gitDir": "test/corpus/repos/javascript", - "sha2": "9a58027ba05317961196f113c79ea9ffad926b20" -} -,{ - "testCaseDescription": "javascript-variable-delete-replacement-test", - "expectedResult": { - "changes": { - "variable.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "variable.js", - "end": [ - 1, - 8 - ] - } - }, - "summary": "Deleted the 'theVar2' identifier", - "tag": "JSONSummary" - }, - { - "span": { - "this": { - "start": [ - 2, - 1 - ], - "name": "variable.js", - "end": [ - 2, - 7 - ] - } - }, - "summary": "Deleted the 'theVar' identifier", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "variable.js", - "end": [ - 2, - 8 - ] - } - }, - "summary": "Added the 'theVar2' identifier", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "variable.js" - ], - "sha1": "9a58027ba05317961196f113c79ea9ffad926b20", - "gitDir": "test/corpus/repos/javascript", - "sha2": "eaebf72a40c5b5efa51afefa013498ddf1954821" -} -,{ - "testCaseDescription": "javascript-variable-delete-test", - "expectedResult": { - "changes": { - "variable.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "variable.js", - "end": [ - 1, - 7 - ] - } - }, - "summary": "Deleted the 'theVar' identifier", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "variable.js" - ], - "sha1": "eaebf72a40c5b5efa51afefa013498ddf1954821", - "gitDir": "test/corpus/repos/javascript", - "sha2": "6a047726509cb5ca3ac81e6bff6d14f65205196b" -} -,{ - "testCaseDescription": "javascript-variable-delete-rest-test", - "expectedResult": { - "changes": { - "variable.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "variable.js", - "end": [ - 1, - 8 - ] - } - }, - "summary": "Deleted the 'theVar2' identifier", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "variable.js" - ], - "sha1": "6a047726509cb5ca3ac81e6bff6d14f65205196b", - "gitDir": "test/corpus/repos/javascript", - "sha2": "e117ae3f5e0945e0d8e971f7bbc0397229a45648" -}] diff --git a/test/corpus/diff-summaries/javascript/void-operator.json b/test/corpus/diff-summaries/javascript/void-operator.json deleted file mode 100644 index 8f3b4a663..000000000 --- a/test/corpus/diff-summaries/javascript/void-operator.json +++ /dev/null @@ -1,308 +0,0 @@ -[{ - "testCaseDescription": "javascript-void-operator-insert-test", - "expectedResult": { - "changes": { - "void-operator.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "void-operator.js", - "end": [ - 1, - 9 - ] - } - }, - "summary": "Added the 'void b()' operator", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "void-operator.js" - ], - "sha1": "91bb86f2c473fce6ff1ddd4c4e25a6362131920f", - "gitDir": "test/corpus/repos/javascript", - "sha2": "e235fe3056b7c71256b661b0a336a44da2be1329" -} -,{ - "testCaseDescription": "javascript-void-operator-replacement-insert-test", - "expectedResult": { - "changes": { - "void-operator.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "void-operator.js", - "end": [ - 1, - 9 - ] - } - }, - "summary": "Added the 'void c()' operator", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "void-operator.js", - "end": [ - 2, - 9 - ] - } - }, - "summary": "Added the 'void b()' operator", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "void-operator.js" - ], - "sha1": "e235fe3056b7c71256b661b0a336a44da2be1329", - "gitDir": "test/corpus/repos/javascript", - "sha2": "f17f509d54fab1faf744a724bea1e6bc45f88ef1" -} -,{ - "testCaseDescription": "javascript-void-operator-delete-insert-test", - "expectedResult": { - "changes": { - "void-operator.js": [ - { - "span": { - "these": [ - { - "start": [ - 1, - 6 - ], - "name": "void-operator.js", - "end": [ - 1, - 7 - ] - }, - { - "start": [ - 1, - 6 - ], - "name": "void-operator.js", - "end": [ - 1, - 7 - ] - } - ] - }, - "summary": "Replaced the 'c' identifier with the 'b' identifier in the b() function call", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "void-operator.js" - ], - "sha1": "f17f509d54fab1faf744a724bea1e6bc45f88ef1", - "gitDir": "test/corpus/repos/javascript", - "sha2": "27ce188eaba0b82b104b61399b6d52e85c9f2934" -} -,{ - "testCaseDescription": "javascript-void-operator-replacement-test", - "expectedResult": { - "changes": { - "void-operator.js": [ - { - "span": { - "these": [ - { - "start": [ - 1, - 6 - ], - "name": "void-operator.js", - "end": [ - 1, - 7 - ] - }, - { - "start": [ - 1, - 6 - ], - "name": "void-operator.js", - "end": [ - 1, - 7 - ] - } - ] - }, - "summary": "Replaced the 'b' identifier with the 'c' identifier in the c() function call", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "void-operator.js" - ], - "sha1": "27ce188eaba0b82b104b61399b6d52e85c9f2934", - "gitDir": "test/corpus/repos/javascript", - "sha2": "b88d743bc3413c7955a22108d0b1c5f52b1eedfd" -} -,{ - "testCaseDescription": "javascript-void-operator-delete-replacement-test", - "expectedResult": { - "changes": { - "void-operator.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "void-operator.js", - "end": [ - 1, - 9 - ] - } - }, - "summary": "Deleted the 'void c()' operator", - "tag": "JSONSummary" - }, - { - "span": { - "this": { - "start": [ - 2, - 1 - ], - "name": "void-operator.js", - "end": [ - 2, - 9 - ] - } - }, - "summary": "Deleted the 'void b()' operator", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "void-operator.js", - "end": [ - 2, - 9 - ] - } - }, - "summary": "Added the 'void c()' operator", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "void-operator.js" - ], - "sha1": "b88d743bc3413c7955a22108d0b1c5f52b1eedfd", - "gitDir": "test/corpus/repos/javascript", - "sha2": "e77413f973aacde76e8f7b65832eda2e3d83c299" -} -,{ - "testCaseDescription": "javascript-void-operator-delete-test", - "expectedResult": { - "changes": { - "void-operator.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "void-operator.js", - "end": [ - 1, - 9 - ] - } - }, - "summary": "Deleted the 'void b()' operator", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "void-operator.js" - ], - "sha1": "e77413f973aacde76e8f7b65832eda2e3d83c299", - "gitDir": "test/corpus/repos/javascript", - "sha2": "57baa35e51004dd414a0bc651d9bb199d393d9a8" -} -,{ - "testCaseDescription": "javascript-void-operator-delete-rest-test", - "expectedResult": { - "changes": { - "void-operator.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "void-operator.js", - "end": [ - 1, - 9 - ] - } - }, - "summary": "Deleted the 'void c()' operator", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "void-operator.js" - ], - "sha1": "57baa35e51004dd414a0bc651d9bb199d393d9a8", - "gitDir": "test/corpus/repos/javascript", - "sha2": "74f192419bb6a3a7ef68bb5eb4cf71e89e09b919" -}] diff --git a/test/corpus/diff-summaries/javascript/while-statement.json b/test/corpus/diff-summaries/javascript/while-statement.json deleted file mode 100644 index d78707ef5..000000000 --- a/test/corpus/diff-summaries/javascript/while-statement.json +++ /dev/null @@ -1,368 +0,0 @@ -[{ - "testCaseDescription": "javascript-while-statement-insert-test", - "expectedResult": { - "changes": { - "while-statement.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "while-statement.js", - "end": [ - 1, - 19 - ] - } - }, - "summary": "Added the 'a' while statement", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "while-statement.js" - ], - "sha1": "1e95946698829d93a91686c01b91618eb065b077", - "gitDir": "test/corpus/repos/javascript", - "sha2": "003db95c9c468101af6b2a4d74708ad5cfcaeac3" -} -,{ - "testCaseDescription": "javascript-while-statement-replacement-insert-test", - "expectedResult": { - "changes": { - "while-statement.js": [ - { - "span": { - "that": { - "start": [ - 1, - 1 - ], - "name": "while-statement.js", - "end": [ - 1, - 19 - ] - } - }, - "summary": "Added the 'b' while statement", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "while-statement.js", - "end": [ - 2, - 19 - ] - } - }, - "summary": "Added the 'a' while statement", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "while-statement.js" - ], - "sha1": "003db95c9c468101af6b2a4d74708ad5cfcaeac3", - "gitDir": "test/corpus/repos/javascript", - "sha2": "898d1deeb737fc056929282ccce44a7aaef55034" -} -,{ - "testCaseDescription": "javascript-while-statement-delete-insert-test", - "expectedResult": { - "changes": { - "while-statement.js": [ - { - "span": { - "these": [ - { - "start": [ - 1, - 8 - ], - "name": "while-statement.js", - "end": [ - 1, - 9 - ] - }, - { - "start": [ - 1, - 8 - ], - "name": "while-statement.js", - "end": [ - 1, - 9 - ] - } - ] - }, - "summary": "Replaced the 'b' identifier with the 'a' identifier", - "tag": "JSONSummary" - }, - { - "span": { - "these": [ - { - "start": [ - 1, - 13 - ], - "name": "while-statement.js", - "end": [ - 1, - 14 - ] - }, - { - "start": [ - 1, - 13 - ], - "name": "while-statement.js", - "end": [ - 1, - 14 - ] - } - ] - }, - "summary": "Replaced the 'a' identifier with the 'b' identifier in the b() function call", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "while-statement.js" - ], - "sha1": "898d1deeb737fc056929282ccce44a7aaef55034", - "gitDir": "test/corpus/repos/javascript", - "sha2": "77e4e9b64b3327f448bb03592ae0db023aa4aa1d" -} -,{ - "testCaseDescription": "javascript-while-statement-replacement-test", - "expectedResult": { - "changes": { - "while-statement.js": [ - { - "span": { - "these": [ - { - "start": [ - 1, - 8 - ], - "name": "while-statement.js", - "end": [ - 1, - 9 - ] - }, - { - "start": [ - 1, - 8 - ], - "name": "while-statement.js", - "end": [ - 1, - 9 - ] - } - ] - }, - "summary": "Replaced the 'a' identifier with the 'b' identifier", - "tag": "JSONSummary" - }, - { - "span": { - "these": [ - { - "start": [ - 1, - 13 - ], - "name": "while-statement.js", - "end": [ - 1, - 14 - ] - }, - { - "start": [ - 1, - 13 - ], - "name": "while-statement.js", - "end": [ - 1, - 14 - ] - } - ] - }, - "summary": "Replaced the 'b' identifier with the 'a' identifier in the a() function call", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "while-statement.js" - ], - "sha1": "77e4e9b64b3327f448bb03592ae0db023aa4aa1d", - "gitDir": "test/corpus/repos/javascript", - "sha2": "6c00977dc68dc8709bce328c2cc8bfb7205793ff" -} -,{ - "testCaseDescription": "javascript-while-statement-delete-replacement-test", - "expectedResult": { - "changes": { - "while-statement.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "while-statement.js", - "end": [ - 1, - 19 - ] - } - }, - "summary": "Deleted the 'b' while statement", - "tag": "JSONSummary" - }, - { - "span": { - "this": { - "start": [ - 2, - 1 - ], - "name": "while-statement.js", - "end": [ - 2, - 19 - ] - } - }, - "summary": "Deleted the 'a' while statement", - "tag": "JSONSummary" - }, - { - "span": { - "that": { - "start": [ - 2, - 1 - ], - "name": "while-statement.js", - "end": [ - 2, - 19 - ] - } - }, - "summary": "Added the 'b' while statement", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "while-statement.js" - ], - "sha1": "6c00977dc68dc8709bce328c2cc8bfb7205793ff", - "gitDir": "test/corpus/repos/javascript", - "sha2": "494bd2f0826ef9bb743f7873c597ed76a7714ec8" -} -,{ - "testCaseDescription": "javascript-while-statement-delete-test", - "expectedResult": { - "changes": { - "while-statement.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "while-statement.js", - "end": [ - 1, - 19 - ] - } - }, - "summary": "Deleted the 'a' while statement", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "while-statement.js" - ], - "sha1": "494bd2f0826ef9bb743f7873c597ed76a7714ec8", - "gitDir": "test/corpus/repos/javascript", - "sha2": "98b4204c2fe7fb408f6c5911ce1a275af862f443" -} -,{ - "testCaseDescription": "javascript-while-statement-delete-rest-test", - "expectedResult": { - "changes": { - "while-statement.js": [ - { - "span": { - "this": { - "start": [ - 1, - 1 - ], - "name": "while-statement.js", - "end": [ - 1, - 19 - ] - } - }, - "summary": "Deleted the 'b' while statement", - "tag": "JSONSummary" - } - ] - }, - "errors": {} - }, - "filePaths": [ - "while-statement.js" - ], - "sha1": "98b4204c2fe7fb408f6c5911ce1a275af862f443", - "gitDir": "test/corpus/repos/javascript", - "sha2": "a373c4a7201be2aa145e60cf15e0adfedc85aac5" -}] From 399d01af9747b2cf6b00b7ceb40a46baee17f227 Mon Sep 17 00:00:00 2001 From: joshvera Date: Tue, 11 Oct 2016 11:12:20 -0400 Subject: [PATCH 15/27] update tests --- .../javascript/anonymous-function.json | 488 ++++++++++++++ .../anonymous-parameterless-function.json | 308 +++++++++ .../diff-summaries/javascript/array.json | 282 ++++++++ .../javascript/arrow-function.json | 308 +++++++++ .../diff-summaries/javascript/assignment.json | 308 +++++++++ .../javascript/bitwise-operator.json | 308 +++++++++ .../javascript/boolean-operator.json | 208 ++++++ .../javascript/chained-callbacks.json | 428 ++++++++++++ .../javascript/chained-property-access.json | 368 +++++++++++ .../diff-summaries/javascript/class.json | 428 ++++++++++++ .../javascript/comma-operator.json | 418 ++++++++++++ .../diff-summaries/javascript/comment.json | 308 +++++++++ .../javascript/constructor-call.json | 308 +++++++++ .../javascript/delete-operator.json | 308 +++++++++ .../javascript/do-while-statement.json | 368 +++++++++++ .../diff-summaries/javascript/false.json | 316 +++++++++ .../javascript/for-in-statement.json | 428 ++++++++++++ .../for-loop-with-in-statement.json | 368 +++++++++++ .../javascript/for-of-statement.json | 428 ++++++++++++ .../javascript/for-statement.json | 308 +++++++++ .../javascript/function-call-args.json | 608 ++++++++++++++++++ .../javascript/function-call.json | 308 +++++++++ .../diff-summaries/javascript/function.json | 308 +++++++++ .../javascript/generator-function.json | 308 +++++++++ .../diff-summaries/javascript/identifier.json | 308 +++++++++ .../diff-summaries/javascript/if-else.json | 308 +++++++++ test/corpus/diff-summaries/javascript/if.json | 308 +++++++++ .../javascript/math-assignment-operator.json | 308 +++++++++ .../javascript/math-operator.json | 368 +++++++++++ .../javascript/member-access-assignment.json | 308 +++++++++ .../javascript/member-access.json | 308 +++++++++ .../javascript/method-call.json | 308 +++++++++ .../javascript/named-function.json | 444 +++++++++++++ .../javascript/nested-functions.json | 368 +++++++++++ .../diff-summaries/javascript/null.json | 316 +++++++++ .../diff-summaries/javascript/number.json | 308 +++++++++ .../javascript/object-with-methods.json | 308 +++++++++ .../diff-summaries/javascript/object.json | 316 +++++++++ .../diff-summaries/javascript/regex.json | 308 +++++++++ .../javascript/relational-operator.json | 208 ++++++ .../javascript/return-statement.json | 282 ++++++++ .../diff-summaries/javascript/string.json | 308 +++++++++ .../subscript-access-assignment.json | 308 +++++++++ .../javascript/subscript-access-string.json | 308 +++++++++ .../javascript/subscript-access-variable.json | 308 +++++++++ .../javascript/switch-statement.json | 368 +++++++++++ .../javascript/template-string.json | 308 +++++++++ .../diff-summaries/javascript/ternary.json | 316 +++++++++ .../javascript/this-expression.json | 316 +++++++++ .../javascript/throw-statement.json | 308 +++++++++ .../diff-summaries/javascript/true.json | 316 +++++++++ .../javascript/try-statement.json | 368 +++++++++++ .../javascript/type-operator.json | 282 ++++++++ .../diff-summaries/javascript/undefined.json | 316 +++++++++ .../javascript/var-declaration.json | 512 +++++++++++++++ .../diff-summaries/javascript/variable.json | 308 +++++++++ .../javascript/void-operator.json | 308 +++++++++ .../javascript/while-statement.json | 368 +++++++++++ test/corpus/repos/javascript | 2 +- 59 files changed, 19533 insertions(+), 1 deletion(-) create mode 100644 test/corpus/diff-summaries/javascript/anonymous-function.json create mode 100644 test/corpus/diff-summaries/javascript/anonymous-parameterless-function.json create mode 100644 test/corpus/diff-summaries/javascript/array.json create mode 100644 test/corpus/diff-summaries/javascript/arrow-function.json create mode 100644 test/corpus/diff-summaries/javascript/assignment.json create mode 100644 test/corpus/diff-summaries/javascript/bitwise-operator.json create mode 100644 test/corpus/diff-summaries/javascript/boolean-operator.json create mode 100644 test/corpus/diff-summaries/javascript/chained-callbacks.json create mode 100644 test/corpus/diff-summaries/javascript/chained-property-access.json create mode 100644 test/corpus/diff-summaries/javascript/class.json create mode 100644 test/corpus/diff-summaries/javascript/comma-operator.json create mode 100644 test/corpus/diff-summaries/javascript/comment.json create mode 100644 test/corpus/diff-summaries/javascript/constructor-call.json create mode 100644 test/corpus/diff-summaries/javascript/delete-operator.json create mode 100644 test/corpus/diff-summaries/javascript/do-while-statement.json create mode 100644 test/corpus/diff-summaries/javascript/false.json create mode 100644 test/corpus/diff-summaries/javascript/for-in-statement.json create mode 100644 test/corpus/diff-summaries/javascript/for-loop-with-in-statement.json create mode 100644 test/corpus/diff-summaries/javascript/for-of-statement.json create mode 100644 test/corpus/diff-summaries/javascript/for-statement.json create mode 100644 test/corpus/diff-summaries/javascript/function-call-args.json create mode 100644 test/corpus/diff-summaries/javascript/function-call.json create mode 100644 test/corpus/diff-summaries/javascript/function.json create mode 100644 test/corpus/diff-summaries/javascript/generator-function.json create mode 100644 test/corpus/diff-summaries/javascript/identifier.json create mode 100644 test/corpus/diff-summaries/javascript/if-else.json create mode 100644 test/corpus/diff-summaries/javascript/if.json create mode 100644 test/corpus/diff-summaries/javascript/math-assignment-operator.json create mode 100644 test/corpus/diff-summaries/javascript/math-operator.json create mode 100644 test/corpus/diff-summaries/javascript/member-access-assignment.json create mode 100644 test/corpus/diff-summaries/javascript/member-access.json create mode 100644 test/corpus/diff-summaries/javascript/method-call.json create mode 100644 test/corpus/diff-summaries/javascript/named-function.json create mode 100644 test/corpus/diff-summaries/javascript/nested-functions.json create mode 100644 test/corpus/diff-summaries/javascript/null.json create mode 100644 test/corpus/diff-summaries/javascript/number.json create mode 100644 test/corpus/diff-summaries/javascript/object-with-methods.json create mode 100644 test/corpus/diff-summaries/javascript/object.json create mode 100644 test/corpus/diff-summaries/javascript/regex.json create mode 100644 test/corpus/diff-summaries/javascript/relational-operator.json create mode 100644 test/corpus/diff-summaries/javascript/return-statement.json create mode 100644 test/corpus/diff-summaries/javascript/string.json create mode 100644 test/corpus/diff-summaries/javascript/subscript-access-assignment.json create mode 100644 test/corpus/diff-summaries/javascript/subscript-access-string.json create mode 100644 test/corpus/diff-summaries/javascript/subscript-access-variable.json create mode 100644 test/corpus/diff-summaries/javascript/switch-statement.json create mode 100644 test/corpus/diff-summaries/javascript/template-string.json create mode 100644 test/corpus/diff-summaries/javascript/ternary.json create mode 100644 test/corpus/diff-summaries/javascript/this-expression.json create mode 100644 test/corpus/diff-summaries/javascript/throw-statement.json create mode 100644 test/corpus/diff-summaries/javascript/true.json create mode 100644 test/corpus/diff-summaries/javascript/try-statement.json create mode 100644 test/corpus/diff-summaries/javascript/type-operator.json create mode 100644 test/corpus/diff-summaries/javascript/undefined.json create mode 100644 test/corpus/diff-summaries/javascript/var-declaration.json create mode 100644 test/corpus/diff-summaries/javascript/variable.json create mode 100644 test/corpus/diff-summaries/javascript/void-operator.json create mode 100644 test/corpus/diff-summaries/javascript/while-statement.json diff --git a/test/corpus/diff-summaries/javascript/anonymous-function.json b/test/corpus/diff-summaries/javascript/anonymous-function.json new file mode 100644 index 000000000..f034da116 --- /dev/null +++ b/test/corpus/diff-summaries/javascript/anonymous-function.json @@ -0,0 +1,488 @@ +[{ + "testCaseDescription": "javascript-anonymous-function-insert-test", + "expectedResult": { + "changes": { + "anonymous-function.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "anonymous-function.js", + "end": [ + 1, + 32 + ] + } + }, + "summary": "Added an anonymous(a, b) function", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "anonymous-function.js" + ], + "sha1": "a0404e9e7b61466d953a033ff444c10691cea549", + "gitDir": "test/corpus/repos/javascript", + "sha2": "1961f9a7fb461c1318e0b6c46b61fc897fa1560b" +} +,{ + "testCaseDescription": "javascript-anonymous-function-replacement-insert-test", + "expectedResult": { + "changes": { + "anonymous-function.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "anonymous-function.js", + "end": [ + 1, + 32 + ] + } + }, + "summary": "Added an anonymous(b, c) function", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "anonymous-function.js", + "end": [ + 2, + 32 + ] + } + }, + "summary": "Added an anonymous(a, b) function", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "anonymous-function.js" + ], + "sha1": "1961f9a7fb461c1318e0b6c46b61fc897fa1560b", + "gitDir": "test/corpus/repos/javascript", + "sha2": "a87c5f91d1af023c750e53541117a0d019b49ed9" +} +,{ + "testCaseDescription": "javascript-anonymous-function-delete-insert-test", + "expectedResult": { + "changes": { + "anonymous-function.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 10 + ], + "name": "anonymous-function.js", + "end": [ + 1, + 11 + ] + }, + { + "start": [ + 1, + 10 + ], + "name": "anonymous-function.js", + "end": [ + 1, + 11 + ] + } + ] + }, + "summary": "Replaced the 'b' identifier with the 'a' identifier", + "tag": "JSONSummary" + }, + { + "span": { + "these": [ + { + "start": [ + 1, + 12 + ], + "name": "anonymous-function.js", + "end": [ + 1, + 13 + ] + }, + { + "start": [ + 1, + 12 + ], + "name": "anonymous-function.js", + "end": [ + 1, + 13 + ] + } + ] + }, + "summary": "Replaced the 'c' identifier with the 'b' identifier", + "tag": "JSONSummary" + }, + { + "span": { + "these": [ + { + "start": [ + 1, + 24 + ], + "name": "anonymous-function.js", + "end": [ + 1, + 25 + ] + }, + { + "start": [ + 1, + 24 + ], + "name": "anonymous-function.js", + "end": [ + 1, + 25 + ] + } + ] + }, + "summary": "Replaced the 'b' identifier with the 'a' identifier", + "tag": "JSONSummary" + }, + { + "span": { + "these": [ + { + "start": [ + 1, + 28 + ], + "name": "anonymous-function.js", + "end": [ + 1, + 29 + ] + }, + { + "start": [ + 1, + 28 + ], + "name": "anonymous-function.js", + "end": [ + 1, + 29 + ] + } + ] + }, + "summary": "Replaced the 'c' identifier with the 'b' identifier", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "anonymous-function.js" + ], + "sha1": "a87c5f91d1af023c750e53541117a0d019b49ed9", + "gitDir": "test/corpus/repos/javascript", + "sha2": "ae9ec1df052f843a7f32f581fa51fecfee985b33" +} +,{ + "testCaseDescription": "javascript-anonymous-function-replacement-test", + "expectedResult": { + "changes": { + "anonymous-function.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 10 + ], + "name": "anonymous-function.js", + "end": [ + 1, + 11 + ] + }, + { + "start": [ + 1, + 10 + ], + "name": "anonymous-function.js", + "end": [ + 1, + 11 + ] + } + ] + }, + "summary": "Replaced the 'a' identifier with the 'b' identifier", + "tag": "JSONSummary" + }, + { + "span": { + "these": [ + { + "start": [ + 1, + 12 + ], + "name": "anonymous-function.js", + "end": [ + 1, + 13 + ] + }, + { + "start": [ + 1, + 12 + ], + "name": "anonymous-function.js", + "end": [ + 1, + 13 + ] + } + ] + }, + "summary": "Replaced the 'b' identifier with the 'c' identifier", + "tag": "JSONSummary" + }, + { + "span": { + "these": [ + { + "start": [ + 1, + 24 + ], + "name": "anonymous-function.js", + "end": [ + 1, + 25 + ] + }, + { + "start": [ + 1, + 24 + ], + "name": "anonymous-function.js", + "end": [ + 1, + 25 + ] + } + ] + }, + "summary": "Replaced the 'a' identifier with the 'b' identifier", + "tag": "JSONSummary" + }, + { + "span": { + "these": [ + { + "start": [ + 1, + 28 + ], + "name": "anonymous-function.js", + "end": [ + 1, + 29 + ] + }, + { + "start": [ + 1, + 28 + ], + "name": "anonymous-function.js", + "end": [ + 1, + 29 + ] + } + ] + }, + "summary": "Replaced the 'b' identifier with the 'c' identifier", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "anonymous-function.js" + ], + "sha1": "ae9ec1df052f843a7f32f581fa51fecfee985b33", + "gitDir": "test/corpus/repos/javascript", + "sha2": "97a65badadc090ac8798ea1710c611c32c6521fa" +} +,{ + "testCaseDescription": "javascript-anonymous-function-delete-replacement-test", + "expectedResult": { + "changes": { + "anonymous-function.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "anonymous-function.js", + "end": [ + 1, + 32 + ] + } + }, + "summary": "Deleted an anonymous(b, c) function", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 1 + ], + "name": "anonymous-function.js", + "end": [ + 2, + 32 + ] + } + }, + "summary": "Deleted an anonymous(a, b) function", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "anonymous-function.js", + "end": [ + 2, + 32 + ] + } + }, + "summary": "Added an anonymous(b, c) function", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "anonymous-function.js" + ], + "sha1": "97a65badadc090ac8798ea1710c611c32c6521fa", + "gitDir": "test/corpus/repos/javascript", + "sha2": "7aa2ca6547621b95a8648317f5824a147b42ab6c" +} +,{ + "testCaseDescription": "javascript-anonymous-function-delete-test", + "expectedResult": { + "changes": { + "anonymous-function.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "anonymous-function.js", + "end": [ + 1, + 32 + ] + } + }, + "summary": "Deleted an anonymous(a, b) function", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "anonymous-function.js" + ], + "sha1": "7aa2ca6547621b95a8648317f5824a147b42ab6c", + "gitDir": "test/corpus/repos/javascript", + "sha2": "77a404dd843047629e7c0f3d1e7e59b97dc14278" +} +,{ + "testCaseDescription": "javascript-anonymous-function-delete-rest-test", + "expectedResult": { + "changes": { + "anonymous-function.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "anonymous-function.js", + "end": [ + 1, + 32 + ] + } + }, + "summary": "Deleted an anonymous(b, c) function", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "anonymous-function.js" + ], + "sha1": "77a404dd843047629e7c0f3d1e7e59b97dc14278", + "gitDir": "test/corpus/repos/javascript", + "sha2": "cbe8e933001ed566c983447bd68c559b8a0ce299" +}] diff --git a/test/corpus/diff-summaries/javascript/anonymous-parameterless-function.json b/test/corpus/diff-summaries/javascript/anonymous-parameterless-function.json new file mode 100644 index 000000000..3b58d4cd4 --- /dev/null +++ b/test/corpus/diff-summaries/javascript/anonymous-parameterless-function.json @@ -0,0 +1,308 @@ +[{ + "testCaseDescription": "javascript-anonymous-parameterless-function-insert-test", + "expectedResult": { + "changes": { + "anonymous-parameterless-function.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "anonymous-parameterless-function.js", + "end": [ + 1, + 28 + ] + } + }, + "summary": "Added an anonymous() function", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "anonymous-parameterless-function.js" + ], + "sha1": "cbe8e933001ed566c983447bd68c559b8a0ce299", + "gitDir": "test/corpus/repos/javascript", + "sha2": "c04c265e97a0a02caf81a65d81ddd315928ebfd6" +} +,{ + "testCaseDescription": "javascript-anonymous-parameterless-function-replacement-insert-test", + "expectedResult": { + "changes": { + "anonymous-parameterless-function.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "anonymous-parameterless-function.js", + "end": [ + 1, + 31 + ] + } + }, + "summary": "Added an anonymous() function", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "anonymous-parameterless-function.js", + "end": [ + 2, + 28 + ] + } + }, + "summary": "Added an anonymous() function", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "anonymous-parameterless-function.js" + ], + "sha1": "c04c265e97a0a02caf81a65d81ddd315928ebfd6", + "gitDir": "test/corpus/repos/javascript", + "sha2": "d7a616f801c122aff974bdd825ffe1bb51c5a8e8" +} +,{ + "testCaseDescription": "javascript-anonymous-parameterless-function-delete-insert-test", + "expectedResult": { + "changes": { + "anonymous-parameterless-function.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 21 + ], + "name": "anonymous-parameterless-function.js", + "end": [ + 1, + 28 + ] + }, + { + "start": [ + 1, + 21 + ], + "name": "anonymous-parameterless-function.js", + "end": [ + 1, + 25 + ] + } + ] + }, + "summary": "Replaced the 'hello' string with the 'hi' string", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "anonymous-parameterless-function.js" + ], + "sha1": "d7a616f801c122aff974bdd825ffe1bb51c5a8e8", + "gitDir": "test/corpus/repos/javascript", + "sha2": "14d2f7d564ac1e8c0d2ca9960c9f42fcaf70f1fa" +} +,{ + "testCaseDescription": "javascript-anonymous-parameterless-function-replacement-test", + "expectedResult": { + "changes": { + "anonymous-parameterless-function.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 21 + ], + "name": "anonymous-parameterless-function.js", + "end": [ + 1, + 25 + ] + }, + { + "start": [ + 1, + 21 + ], + "name": "anonymous-parameterless-function.js", + "end": [ + 1, + 28 + ] + } + ] + }, + "summary": "Replaced the 'hi' string with the 'hello' string", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "anonymous-parameterless-function.js" + ], + "sha1": "14d2f7d564ac1e8c0d2ca9960c9f42fcaf70f1fa", + "gitDir": "test/corpus/repos/javascript", + "sha2": "24aaf302c042840e41e709b2d1b4b9310c1f3dac" +} +,{ + "testCaseDescription": "javascript-anonymous-parameterless-function-delete-replacement-test", + "expectedResult": { + "changes": { + "anonymous-parameterless-function.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "anonymous-parameterless-function.js", + "end": [ + 1, + 31 + ] + } + }, + "summary": "Deleted an anonymous() function", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 1 + ], + "name": "anonymous-parameterless-function.js", + "end": [ + 2, + 28 + ] + } + }, + "summary": "Deleted an anonymous() function", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "anonymous-parameterless-function.js", + "end": [ + 2, + 31 + ] + } + }, + "summary": "Added an anonymous() function", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "anonymous-parameterless-function.js" + ], + "sha1": "24aaf302c042840e41e709b2d1b4b9310c1f3dac", + "gitDir": "test/corpus/repos/javascript", + "sha2": "dc90b671f97861fbcd6f3589c51c7d533183fd48" +} +,{ + "testCaseDescription": "javascript-anonymous-parameterless-function-delete-test", + "expectedResult": { + "changes": { + "anonymous-parameterless-function.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "anonymous-parameterless-function.js", + "end": [ + 1, + 28 + ] + } + }, + "summary": "Deleted an anonymous() function", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "anonymous-parameterless-function.js" + ], + "sha1": "dc90b671f97861fbcd6f3589c51c7d533183fd48", + "gitDir": "test/corpus/repos/javascript", + "sha2": "40ac908bb69f7662e5fe092a8c3f5af80a5ea195" +} +,{ + "testCaseDescription": "javascript-anonymous-parameterless-function-delete-rest-test", + "expectedResult": { + "changes": { + "anonymous-parameterless-function.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "anonymous-parameterless-function.js", + "end": [ + 1, + 31 + ] + } + }, + "summary": "Deleted an anonymous() function", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "anonymous-parameterless-function.js" + ], + "sha1": "40ac908bb69f7662e5fe092a8c3f5af80a5ea195", + "gitDir": "test/corpus/repos/javascript", + "sha2": "a7028eef7c56f7ba5c5dda0faadcfffe205d5a40" +}] diff --git a/test/corpus/diff-summaries/javascript/array.json b/test/corpus/diff-summaries/javascript/array.json new file mode 100644 index 000000000..bb27e911c --- /dev/null +++ b/test/corpus/diff-summaries/javascript/array.json @@ -0,0 +1,282 @@ +[{ + "testCaseDescription": "javascript-array-insert-test", + "expectedResult": { + "changes": { + "array.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "array.js", + "end": [ + 1, + 12 + ] + } + }, + "summary": "Added the '[ \"item1\" ]' array", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "array.js" + ], + "sha1": "6c3b6d5c7d426a657e90d97cdfd248b2453bc087", + "gitDir": "test/corpus/repos/javascript", + "sha2": "3445abbd9210b7d4d23872fdf2614b77c3e464bd" +} +,{ + "testCaseDescription": "javascript-array-replacement-insert-test", + "expectedResult": { + "changes": { + "array.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "array.js", + "end": [ + 1, + 21 + ] + } + }, + "summary": "Added the '[ \"item1\", \"item2\" ]' array", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "array.js", + "end": [ + 2, + 12 + ] + } + }, + "summary": "Added the '[ \"item1\" ]' array", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "array.js" + ], + "sha1": "3445abbd9210b7d4d23872fdf2614b77c3e464bd", + "gitDir": "test/corpus/repos/javascript", + "sha2": "7d3cd095cf340ccda50bd7dae0405288a27d6a28" +} +,{ + "testCaseDescription": "javascript-array-delete-insert-test", + "expectedResult": { + "changes": { + "array.js": [ + { + "span": { + "this": { + "start": [ + 1, + 12 + ], + "name": "array.js", + "end": [ + 1, + 19 + ] + } + }, + "summary": "Deleted the \"item2\" string", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "array.js" + ], + "sha1": "7d3cd095cf340ccda50bd7dae0405288a27d6a28", + "gitDir": "test/corpus/repos/javascript", + "sha2": "7d1d0e7c6052a06a9bf764a04ca06acff78dffca" +} +,{ + "testCaseDescription": "javascript-array-replacement-test", + "expectedResult": { + "changes": { + "array.js": [ + { + "span": { + "that": { + "start": [ + 1, + 12 + ], + "name": "array.js", + "end": [ + 1, + 19 + ] + } + }, + "summary": "Added the \"item2\" string", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "array.js" + ], + "sha1": "7d1d0e7c6052a06a9bf764a04ca06acff78dffca", + "gitDir": "test/corpus/repos/javascript", + "sha2": "aac7a79ab7aecf3345aea24ea4f38b4915921d8a" +} +,{ + "testCaseDescription": "javascript-array-delete-replacement-test", + "expectedResult": { + "changes": { + "array.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "array.js", + "end": [ + 1, + 21 + ] + } + }, + "summary": "Deleted the '[ \"item1\", \"item2\" ]' array", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 1 + ], + "name": "array.js", + "end": [ + 2, + 12 + ] + } + }, + "summary": "Deleted the '[ \"item1\" ]' array", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "array.js", + "end": [ + 2, + 21 + ] + } + }, + "summary": "Added the '[ \"item1\", \"item2\" ]' array", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "array.js" + ], + "sha1": "aac7a79ab7aecf3345aea24ea4f38b4915921d8a", + "gitDir": "test/corpus/repos/javascript", + "sha2": "24c35a10f9dae3da5d9c331e50fe66b8be896736" +} +,{ + "testCaseDescription": "javascript-array-delete-test", + "expectedResult": { + "changes": { + "array.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "array.js", + "end": [ + 1, + 12 + ] + } + }, + "summary": "Deleted the '[ \"item1\" ]' array", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "array.js" + ], + "sha1": "24c35a10f9dae3da5d9c331e50fe66b8be896736", + "gitDir": "test/corpus/repos/javascript", + "sha2": "84b4a8728ce89f0768b5ea0dcce540a133772e59" +} +,{ + "testCaseDescription": "javascript-array-delete-rest-test", + "expectedResult": { + "changes": { + "array.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "array.js", + "end": [ + 1, + 21 + ] + } + }, + "summary": "Deleted the '[ \"item1\", \"item2\" ]' array", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "array.js" + ], + "sha1": "84b4a8728ce89f0768b5ea0dcce540a133772e59", + "gitDir": "test/corpus/repos/javascript", + "sha2": "7421caaeb3a46acf3fd36871e3fd56e4409df4c1" +}] diff --git a/test/corpus/diff-summaries/javascript/arrow-function.json b/test/corpus/diff-summaries/javascript/arrow-function.json new file mode 100644 index 000000000..5f854ba03 --- /dev/null +++ b/test/corpus/diff-summaries/javascript/arrow-function.json @@ -0,0 +1,308 @@ +[{ + "testCaseDescription": "javascript-arrow-function-insert-test", + "expectedResult": { + "changes": { + "arrow-function.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "arrow-function.js", + "end": [ + 1, + 24 + ] + } + }, + "summary": "Added an anonymous(f, g) function", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "arrow-function.js" + ], + "sha1": "1331d4ffb544aebfa16c17c9c2ebbab19e6f422a", + "gitDir": "test/corpus/repos/javascript", + "sha2": "4d09b922ad63a1acd3b6afe3d68dd6dc22ba78c8" +} +,{ + "testCaseDescription": "javascript-arrow-function-replacement-insert-test", + "expectedResult": { + "changes": { + "arrow-function.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "arrow-function.js", + "end": [ + 1, + 24 + ] + } + }, + "summary": "Added an anonymous(f, g) function", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "arrow-function.js", + "end": [ + 2, + 24 + ] + } + }, + "summary": "Added an anonymous(f, g) function", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "arrow-function.js" + ], + "sha1": "4d09b922ad63a1acd3b6afe3d68dd6dc22ba78c8", + "gitDir": "test/corpus/repos/javascript", + "sha2": "6d4a9c5fe2f6ae81f03bf761385238d96409cd5c" +} +,{ + "testCaseDescription": "javascript-arrow-function-delete-insert-test", + "expectedResult": { + "changes": { + "arrow-function.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 20 + ], + "name": "arrow-function.js", + "end": [ + 1, + 21 + ] + }, + { + "start": [ + 1, + 20 + ], + "name": "arrow-function.js", + "end": [ + 1, + 21 + ] + } + ] + }, + "summary": "Replaced the 'g' identifier with the 'h' identifier", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "arrow-function.js" + ], + "sha1": "6d4a9c5fe2f6ae81f03bf761385238d96409cd5c", + "gitDir": "test/corpus/repos/javascript", + "sha2": "955047d8cae03944863fe0457dab999410da00ee" +} +,{ + "testCaseDescription": "javascript-arrow-function-replacement-test", + "expectedResult": { + "changes": { + "arrow-function.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 20 + ], + "name": "arrow-function.js", + "end": [ + 1, + 21 + ] + }, + { + "start": [ + 1, + 20 + ], + "name": "arrow-function.js", + "end": [ + 1, + 21 + ] + } + ] + }, + "summary": "Replaced the 'h' identifier with the 'g' identifier", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "arrow-function.js" + ], + "sha1": "955047d8cae03944863fe0457dab999410da00ee", + "gitDir": "test/corpus/repos/javascript", + "sha2": "4f886505083883d5ce313d51ae222b05044cb464" +} +,{ + "testCaseDescription": "javascript-arrow-function-delete-replacement-test", + "expectedResult": { + "changes": { + "arrow-function.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "arrow-function.js", + "end": [ + 1, + 24 + ] + } + }, + "summary": "Deleted an anonymous(f, g) function", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 1 + ], + "name": "arrow-function.js", + "end": [ + 2, + 24 + ] + } + }, + "summary": "Deleted an anonymous(f, g) function", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "arrow-function.js", + "end": [ + 2, + 24 + ] + } + }, + "summary": "Added an anonymous(f, g) function", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "arrow-function.js" + ], + "sha1": "4f886505083883d5ce313d51ae222b05044cb464", + "gitDir": "test/corpus/repos/javascript", + "sha2": "3f81a39022968106428052245cf475419ec283b6" +} +,{ + "testCaseDescription": "javascript-arrow-function-delete-test", + "expectedResult": { + "changes": { + "arrow-function.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "arrow-function.js", + "end": [ + 1, + 24 + ] + } + }, + "summary": "Deleted an anonymous(f, g) function", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "arrow-function.js" + ], + "sha1": "3f81a39022968106428052245cf475419ec283b6", + "gitDir": "test/corpus/repos/javascript", + "sha2": "d75e2c071c454713f7824114e29f4d99427c43f5" +} +,{ + "testCaseDescription": "javascript-arrow-function-delete-rest-test", + "expectedResult": { + "changes": { + "arrow-function.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "arrow-function.js", + "end": [ + 1, + 24 + ] + } + }, + "summary": "Deleted an anonymous(f, g) function", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "arrow-function.js" + ], + "sha1": "d75e2c071c454713f7824114e29f4d99427c43f5", + "gitDir": "test/corpus/repos/javascript", + "sha2": "4d63196a05b9443aebe166c10eaf31d60a162f7e" +}] diff --git a/test/corpus/diff-summaries/javascript/assignment.json b/test/corpus/diff-summaries/javascript/assignment.json new file mode 100644 index 000000000..ceec1d68b --- /dev/null +++ b/test/corpus/diff-summaries/javascript/assignment.json @@ -0,0 +1,308 @@ +[{ + "testCaseDescription": "javascript-assignment-insert-test", + "expectedResult": { + "changes": { + "assignment.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "assignment.js", + "end": [ + 1, + 6 + ] + } + }, + "summary": "Added the 'x' assignment", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "assignment.js" + ], + "sha1": "1689419def381340a06222171173117f80ab169e", + "gitDir": "test/corpus/repos/javascript", + "sha2": "b5c863844f2f4c648119688662a2b85e597d6126" +} +,{ + "testCaseDescription": "javascript-assignment-replacement-insert-test", + "expectedResult": { + "changes": { + "assignment.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "assignment.js", + "end": [ + 1, + 6 + ] + } + }, + "summary": "Added the 'x' assignment", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "assignment.js", + "end": [ + 2, + 6 + ] + } + }, + "summary": "Added the 'x' assignment", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "assignment.js" + ], + "sha1": "b5c863844f2f4c648119688662a2b85e597d6126", + "gitDir": "test/corpus/repos/javascript", + "sha2": "a4a65b9fe496e319e6a5419bb406f3f6011e9e21" +} +,{ + "testCaseDescription": "javascript-assignment-delete-insert-test", + "expectedResult": { + "changes": { + "assignment.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 5 + ], + "name": "assignment.js", + "end": [ + 1, + 6 + ] + }, + { + "start": [ + 1, + 5 + ], + "name": "assignment.js", + "end": [ + 1, + 6 + ] + } + ] + }, + "summary": "Replaced '1' with '0' in an assignment to x", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "assignment.js" + ], + "sha1": "a4a65b9fe496e319e6a5419bb406f3f6011e9e21", + "gitDir": "test/corpus/repos/javascript", + "sha2": "aaf8ea43af02716f3eae9d8e2734aa6e59e212e2" +} +,{ + "testCaseDescription": "javascript-assignment-replacement-test", + "expectedResult": { + "changes": { + "assignment.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 5 + ], + "name": "assignment.js", + "end": [ + 1, + 6 + ] + }, + { + "start": [ + 1, + 5 + ], + "name": "assignment.js", + "end": [ + 1, + 6 + ] + } + ] + }, + "summary": "Replaced '0' with '1' in an assignment to x", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "assignment.js" + ], + "sha1": "aaf8ea43af02716f3eae9d8e2734aa6e59e212e2", + "gitDir": "test/corpus/repos/javascript", + "sha2": "85a5c7b18e7333cd721c165391f0a18df4b3bae1" +} +,{ + "testCaseDescription": "javascript-assignment-delete-replacement-test", + "expectedResult": { + "changes": { + "assignment.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "assignment.js", + "end": [ + 1, + 6 + ] + } + }, + "summary": "Deleted the 'x' assignment", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 1 + ], + "name": "assignment.js", + "end": [ + 2, + 6 + ] + } + }, + "summary": "Deleted the 'x' assignment", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "assignment.js", + "end": [ + 2, + 6 + ] + } + }, + "summary": "Added the 'x' assignment", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "assignment.js" + ], + "sha1": "85a5c7b18e7333cd721c165391f0a18df4b3bae1", + "gitDir": "test/corpus/repos/javascript", + "sha2": "afc6f31261dda7281144aceaa36021e6aa5b019c" +} +,{ + "testCaseDescription": "javascript-assignment-delete-test", + "expectedResult": { + "changes": { + "assignment.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "assignment.js", + "end": [ + 1, + 6 + ] + } + }, + "summary": "Deleted the 'x' assignment", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "assignment.js" + ], + "sha1": "afc6f31261dda7281144aceaa36021e6aa5b019c", + "gitDir": "test/corpus/repos/javascript", + "sha2": "a33ab633edb97c7a89d8e43129a98577769e5d15" +} +,{ + "testCaseDescription": "javascript-assignment-delete-rest-test", + "expectedResult": { + "changes": { + "assignment.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "assignment.js", + "end": [ + 1, + 6 + ] + } + }, + "summary": "Deleted the 'x' assignment", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "assignment.js" + ], + "sha1": "a33ab633edb97c7a89d8e43129a98577769e5d15", + "gitDir": "test/corpus/repos/javascript", + "sha2": "6882106e2e1564145c50f664a6446f6c37b1ab3f" +}] diff --git a/test/corpus/diff-summaries/javascript/bitwise-operator.json b/test/corpus/diff-summaries/javascript/bitwise-operator.json new file mode 100644 index 000000000..bceddf51c --- /dev/null +++ b/test/corpus/diff-summaries/javascript/bitwise-operator.json @@ -0,0 +1,308 @@ +[{ + "testCaseDescription": "javascript-bitwise-operator-insert-test", + "expectedResult": { + "changes": { + "bitwise-operator.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "bitwise-operator.js", + "end": [ + 1, + 7 + ] + } + }, + "summary": "Added the 'i >> j' bitwise operator", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "bitwise-operator.js" + ], + "sha1": "c77130c14c2dbfd795136ff0fd27924d67a13e12", + "gitDir": "test/corpus/repos/javascript", + "sha2": "190cbea65dd6ddbe9827c35d43f4cb41a8fa8929" +} +,{ + "testCaseDescription": "javascript-bitwise-operator-replacement-insert-test", + "expectedResult": { + "changes": { + "bitwise-operator.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "bitwise-operator.js", + "end": [ + 1, + 7 + ] + } + }, + "summary": "Added the 'i >> k' bitwise operator", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "bitwise-operator.js", + "end": [ + 2, + 7 + ] + } + }, + "summary": "Added the 'i >> j' bitwise operator", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "bitwise-operator.js" + ], + "sha1": "190cbea65dd6ddbe9827c35d43f4cb41a8fa8929", + "gitDir": "test/corpus/repos/javascript", + "sha2": "f0fa4938e0e1070c42a732d4560110c87c29d66e" +} +,{ + "testCaseDescription": "javascript-bitwise-operator-delete-insert-test", + "expectedResult": { + "changes": { + "bitwise-operator.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 6 + ], + "name": "bitwise-operator.js", + "end": [ + 1, + 7 + ] + }, + { + "start": [ + 1, + 6 + ], + "name": "bitwise-operator.js", + "end": [ + 1, + 7 + ] + } + ] + }, + "summary": "Replaced the 'k' identifier with the 'j' identifier", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "bitwise-operator.js" + ], + "sha1": "f0fa4938e0e1070c42a732d4560110c87c29d66e", + "gitDir": "test/corpus/repos/javascript", + "sha2": "1861e01a938f5df02b33bac4c8da59bbd208f8dc" +} +,{ + "testCaseDescription": "javascript-bitwise-operator-replacement-test", + "expectedResult": { + "changes": { + "bitwise-operator.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 6 + ], + "name": "bitwise-operator.js", + "end": [ + 1, + 7 + ] + }, + { + "start": [ + 1, + 6 + ], + "name": "bitwise-operator.js", + "end": [ + 1, + 7 + ] + } + ] + }, + "summary": "Replaced the 'j' identifier with the 'k' identifier", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "bitwise-operator.js" + ], + "sha1": "1861e01a938f5df02b33bac4c8da59bbd208f8dc", + "gitDir": "test/corpus/repos/javascript", + "sha2": "4daaabf2eb29de89938a05544251cd3edc196c38" +} +,{ + "testCaseDescription": "javascript-bitwise-operator-delete-replacement-test", + "expectedResult": { + "changes": { + "bitwise-operator.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "bitwise-operator.js", + "end": [ + 1, + 7 + ] + } + }, + "summary": "Deleted the 'i >> k' bitwise operator", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 1 + ], + "name": "bitwise-operator.js", + "end": [ + 2, + 7 + ] + } + }, + "summary": "Deleted the 'i >> j' bitwise operator", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "bitwise-operator.js", + "end": [ + 2, + 7 + ] + } + }, + "summary": "Added the 'i >> k' bitwise operator", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "bitwise-operator.js" + ], + "sha1": "4daaabf2eb29de89938a05544251cd3edc196c38", + "gitDir": "test/corpus/repos/javascript", + "sha2": "9e75dc90f18c35f845fbd0d9a398a4b02986b888" +} +,{ + "testCaseDescription": "javascript-bitwise-operator-delete-test", + "expectedResult": { + "changes": { + "bitwise-operator.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "bitwise-operator.js", + "end": [ + 1, + 7 + ] + } + }, + "summary": "Deleted the 'i >> j' bitwise operator", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "bitwise-operator.js" + ], + "sha1": "9e75dc90f18c35f845fbd0d9a398a4b02986b888", + "gitDir": "test/corpus/repos/javascript", + "sha2": "dfd6ce59330ff71c41c66acf43df3e05ec594a1c" +} +,{ + "testCaseDescription": "javascript-bitwise-operator-delete-rest-test", + "expectedResult": { + "changes": { + "bitwise-operator.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "bitwise-operator.js", + "end": [ + 1, + 7 + ] + } + }, + "summary": "Deleted the 'i >> k' bitwise operator", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "bitwise-operator.js" + ], + "sha1": "dfd6ce59330ff71c41c66acf43df3e05ec594a1c", + "gitDir": "test/corpus/repos/javascript", + "sha2": "4a348bc66ccc50e501fe3e49df1cd797d99ca405" +}] diff --git a/test/corpus/diff-summaries/javascript/boolean-operator.json b/test/corpus/diff-summaries/javascript/boolean-operator.json new file mode 100644 index 000000000..c2eb82023 --- /dev/null +++ b/test/corpus/diff-summaries/javascript/boolean-operator.json @@ -0,0 +1,208 @@ +[{ + "testCaseDescription": "javascript-boolean-operator-insert-test", + "expectedResult": { + "changes": { + "boolean-operator.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "boolean-operator.js", + "end": [ + 1, + 7 + ] + } + }, + "summary": "Added the 'i || j' boolean operator", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "boolean-operator.js" + ], + "sha1": "cb37f95870629005756c374dade2599850dc09d3", + "gitDir": "test/corpus/repos/javascript", + "sha2": "feae2d99618470e8d0a6cbe778297c6768e870a2" +} +,{ + "testCaseDescription": "javascript-boolean-operator-replacement-insert-test", + "expectedResult": { + "changes": { + "boolean-operator.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "boolean-operator.js", + "end": [ + 1, + 7 + ] + } + }, + "summary": "Added the 'i && j' boolean operator", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "boolean-operator.js", + "end": [ + 2, + 7 + ] + } + }, + "summary": "Added the 'i || j' boolean operator", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "boolean-operator.js" + ], + "sha1": "feae2d99618470e8d0a6cbe778297c6768e870a2", + "gitDir": "test/corpus/repos/javascript", + "sha2": "0f357662936edfbdcc46648837258c42e48f4f91" +} +,{ + "testCaseDescription": "javascript-boolean-operator-delete-insert-test", + "expectedResult": { + "changes": {}, + "errors": {} + }, + "filePaths": [ + "boolean-operator.js" + ], + "sha1": "0f357662936edfbdcc46648837258c42e48f4f91", + "gitDir": "test/corpus/repos/javascript", + "sha2": "426262cded94a831340aada02d1fd390b5be6370" +} +,{ + "testCaseDescription": "javascript-boolean-operator-replacement-test", + "expectedResult": { + "changes": {}, + "errors": {} + }, + "filePaths": [ + "boolean-operator.js" + ], + "sha1": "426262cded94a831340aada02d1fd390b5be6370", + "gitDir": "test/corpus/repos/javascript", + "sha2": "851b05bfac7dadb37628481d50607d29d8cd6960" +} +,{ + "testCaseDescription": "javascript-boolean-operator-delete-replacement-test", + "expectedResult": { + "changes": { + "boolean-operator.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "boolean-operator.js", + "end": [ + 1, + 7 + ] + } + }, + "summary": "Deleted the 'i && j' boolean operator", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "boolean-operator.js" + ], + "sha1": "851b05bfac7dadb37628481d50607d29d8cd6960", + "gitDir": "test/corpus/repos/javascript", + "sha2": "ae0501cdc7ef28e75317be147919ba8aea8dd12c" +} +,{ + "testCaseDescription": "javascript-boolean-operator-delete-test", + "expectedResult": { + "changes": { + "boolean-operator.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "boolean-operator.js", + "end": [ + 1, + 7 + ] + } + }, + "summary": "Deleted the 'i || j' boolean operator", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "boolean-operator.js" + ], + "sha1": "ae0501cdc7ef28e75317be147919ba8aea8dd12c", + "gitDir": "test/corpus/repos/javascript", + "sha2": "0738acb204f7c855934c15c9aeec04d83f2ea892" +} +,{ + "testCaseDescription": "javascript-boolean-operator-delete-rest-test", + "expectedResult": { + "changes": { + "boolean-operator.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "boolean-operator.js", + "end": [ + 1, + 7 + ] + } + }, + "summary": "Deleted the 'i && j' boolean operator", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "boolean-operator.js" + ], + "sha1": "0738acb204f7c855934c15c9aeec04d83f2ea892", + "gitDir": "test/corpus/repos/javascript", + "sha2": "c77130c14c2dbfd795136ff0fd27924d67a13e12" +}] diff --git a/test/corpus/diff-summaries/javascript/chained-callbacks.json b/test/corpus/diff-summaries/javascript/chained-callbacks.json new file mode 100644 index 000000000..7373441f2 --- /dev/null +++ b/test/corpus/diff-summaries/javascript/chained-callbacks.json @@ -0,0 +1,428 @@ +[{ + "testCaseDescription": "javascript-chained-callbacks-insert-test", + "expectedResult": { + "changes": { + "chained-callbacks.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "chained-callbacks.js", + "end": [ + 1, + 39 + ] + } + }, + "summary": "Added the 'this.map(…)' method call", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "chained-callbacks.js" + ], + "sha1": "26f941c6191463416b1c6a56314b19dfe5d09221", + "gitDir": "test/corpus/repos/javascript", + "sha2": "1feed1cf1d95ca3dd414517b6209f4b939f9a424" +} +,{ + "testCaseDescription": "javascript-chained-callbacks-replacement-insert-test", + "expectedResult": { + "changes": { + "chained-callbacks.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "chained-callbacks.js", + "end": [ + 1, + 42 + ] + } + }, + "summary": "Added the 'this.reduce(…)' method call", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "chained-callbacks.js", + "end": [ + 2, + 39 + ] + } + }, + "summary": "Added the 'this.map(…)' method call", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "chained-callbacks.js" + ], + "sha1": "1feed1cf1d95ca3dd414517b6209f4b939f9a424", + "gitDir": "test/corpus/repos/javascript", + "sha2": "07ee33b6378c5521565478ca27a988226db043bc" +} +,{ + "testCaseDescription": "javascript-chained-callbacks-delete-insert-test", + "expectedResult": { + "changes": { + "chained-callbacks.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 6 + ], + "name": "chained-callbacks.js", + "end": [ + 1, + 12 + ] + }, + { + "start": [ + 1, + 6 + ], + "name": "chained-callbacks.js", + "end": [ + 1, + 9 + ] + } + ] + }, + "summary": "Replaced the 'reduce' identifier with the 'map' identifier in the this.map(…) method call", + "tag": "JSONSummary" + }, + { + "span": { + "these": [ + { + "start": [ + 1, + 35 + ], + "name": "chained-callbacks.js", + "end": [ + 1, + 36 + ] + }, + { + "start": [ + 1, + 32 + ], + "name": "chained-callbacks.js", + "end": [ + 1, + 33 + ] + } + ] + }, + "summary": "Replaced the 'b' identifier with the 'a' identifier in the this.map(…) method call", + "tag": "JSONSummary" + }, + { + "span": { + "these": [ + { + "start": [ + 1, + 37 + ], + "name": "chained-callbacks.js", + "end": [ + 1, + 38 + ] + }, + { + "start": [ + 1, + 34 + ], + "name": "chained-callbacks.js", + "end": [ + 1, + 35 + ] + } + ] + }, + "summary": "Replaced the 'a' identifier with the 'b' identifier in the this.map(…) method call", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "chained-callbacks.js" + ], + "sha1": "07ee33b6378c5521565478ca27a988226db043bc", + "gitDir": "test/corpus/repos/javascript", + "sha2": "cde3100134b868aee4b00d1f76df2be1acced6d0" +} +,{ + "testCaseDescription": "javascript-chained-callbacks-replacement-test", + "expectedResult": { + "changes": { + "chained-callbacks.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 6 + ], + "name": "chained-callbacks.js", + "end": [ + 1, + 9 + ] + }, + { + "start": [ + 1, + 6 + ], + "name": "chained-callbacks.js", + "end": [ + 1, + 12 + ] + } + ] + }, + "summary": "Replaced the 'map' identifier with the 'reduce' identifier in the this.reduce(…) method call", + "tag": "JSONSummary" + }, + { + "span": { + "these": [ + { + "start": [ + 1, + 32 + ], + "name": "chained-callbacks.js", + "end": [ + 1, + 33 + ] + }, + { + "start": [ + 1, + 35 + ], + "name": "chained-callbacks.js", + "end": [ + 1, + 36 + ] + } + ] + }, + "summary": "Replaced the 'a' identifier with the 'b' identifier in the this.reduce(…) method call", + "tag": "JSONSummary" + }, + { + "span": { + "these": [ + { + "start": [ + 1, + 34 + ], + "name": "chained-callbacks.js", + "end": [ + 1, + 35 + ] + }, + { + "start": [ + 1, + 37 + ], + "name": "chained-callbacks.js", + "end": [ + 1, + 38 + ] + } + ] + }, + "summary": "Replaced the 'b' identifier with the 'a' identifier in the this.reduce(…) method call", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "chained-callbacks.js" + ], + "sha1": "cde3100134b868aee4b00d1f76df2be1acced6d0", + "gitDir": "test/corpus/repos/javascript", + "sha2": "6442a64e98e7f30d16e22ee22bcf2586b4cf03a4" +} +,{ + "testCaseDescription": "javascript-chained-callbacks-delete-replacement-test", + "expectedResult": { + "changes": { + "chained-callbacks.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "chained-callbacks.js", + "end": [ + 1, + 42 + ] + } + }, + "summary": "Deleted the 'this.reduce(…)' method call", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 1 + ], + "name": "chained-callbacks.js", + "end": [ + 2, + 39 + ] + } + }, + "summary": "Deleted the 'this.map(…)' method call", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "chained-callbacks.js", + "end": [ + 2, + 42 + ] + } + }, + "summary": "Added the 'this.reduce(…)' method call", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "chained-callbacks.js" + ], + "sha1": "6442a64e98e7f30d16e22ee22bcf2586b4cf03a4", + "gitDir": "test/corpus/repos/javascript", + "sha2": "3bcdf485f97763d63d4c0031d2f780c1a17c014f" +} +,{ + "testCaseDescription": "javascript-chained-callbacks-delete-test", + "expectedResult": { + "changes": { + "chained-callbacks.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "chained-callbacks.js", + "end": [ + 1, + 39 + ] + } + }, + "summary": "Deleted the 'this.map(…)' method call", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "chained-callbacks.js" + ], + "sha1": "3bcdf485f97763d63d4c0031d2f780c1a17c014f", + "gitDir": "test/corpus/repos/javascript", + "sha2": "77aa8df2f2a53b78df109832b331ac606d4eaa30" +} +,{ + "testCaseDescription": "javascript-chained-callbacks-delete-rest-test", + "expectedResult": { + "changes": { + "chained-callbacks.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "chained-callbacks.js", + "end": [ + 1, + 42 + ] + } + }, + "summary": "Deleted the 'this.reduce(…)' method call", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "chained-callbacks.js" + ], + "sha1": "77aa8df2f2a53b78df109832b331ac606d4eaa30", + "gitDir": "test/corpus/repos/javascript", + "sha2": "66f76d6c6d3a517f3f4c016d8e03d3497cf724c6" +}] diff --git a/test/corpus/diff-summaries/javascript/chained-property-access.json b/test/corpus/diff-summaries/javascript/chained-property-access.json new file mode 100644 index 000000000..d237f9f96 --- /dev/null +++ b/test/corpus/diff-summaries/javascript/chained-property-access.json @@ -0,0 +1,368 @@ +[{ + "testCaseDescription": "javascript-chained-property-access-insert-test", + "expectedResult": { + "changes": { + "chained-property-access.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "chained-property-access.js", + "end": [ + 2, + 1 + ] + } + }, + "summary": "Added the 'returned.promise().done(…).fail(…)' return statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "chained-property-access.js" + ], + "sha1": "5172568a010252e98966d57a1c3fc1ade326f9ab", + "gitDir": "test/corpus/repos/javascript", + "sha2": "f59315119ff60b7a5eec00c298a3dbaced0b59d4" +} +,{ + "testCaseDescription": "javascript-chained-property-access-replacement-insert-test", + "expectedResult": { + "changes": { + "chained-property-access.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "chained-property-access.js", + "end": [ + 2, + 1 + ] + } + }, + "summary": "Added the 'returned.promise().done(…).fail(…)' return statement", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "chained-property-access.js", + "end": [ + 3, + 1 + ] + } + }, + "summary": "Added the 'returned.promise().done(…).fail(…)' return statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "chained-property-access.js" + ], + "sha1": "f59315119ff60b7a5eec00c298a3dbaced0b59d4", + "gitDir": "test/corpus/repos/javascript", + "sha2": "8bda63987dd989d6e42ddc5661fe2b22bb0cec77" +} +,{ + "testCaseDescription": "javascript-chained-property-access-delete-insert-test", + "expectedResult": { + "changes": { + "chained-property-access.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 33 + ], + "name": "chained-property-access.js", + "end": [ + 1, + 43 + ] + }, + { + "start": [ + 1, + 33 + ], + "name": "chained-property-access.js", + "end": [ + 1, + 41 + ] + } + ] + }, + "summary": "Replaced the 'otherDefer' identifier with the 'newDefer' identifier in the returned.promise().done(…) method call", + "tag": "JSONSummary" + }, + { + "span": { + "these": [ + { + "start": [ + 1, + 60 + ], + "name": "chained-property-access.js", + "end": [ + 1, + 70 + ] + }, + { + "start": [ + 1, + 58 + ], + "name": "chained-property-access.js", + "end": [ + 1, + 66 + ] + } + ] + }, + "summary": "Replaced the 'otherDefer' identifier with the 'newDefer' identifier in the returned.promise().done(…).fail(…) method call", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "chained-property-access.js" + ], + "sha1": "8bda63987dd989d6e42ddc5661fe2b22bb0cec77", + "gitDir": "test/corpus/repos/javascript", + "sha2": "49366eb9b5adfc0372d1b58a87acd15c8052a606" +} +,{ + "testCaseDescription": "javascript-chained-property-access-replacement-test", + "expectedResult": { + "changes": { + "chained-property-access.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 33 + ], + "name": "chained-property-access.js", + "end": [ + 1, + 41 + ] + }, + { + "start": [ + 1, + 33 + ], + "name": "chained-property-access.js", + "end": [ + 1, + 43 + ] + } + ] + }, + "summary": "Replaced the 'newDefer' identifier with the 'otherDefer' identifier in the returned.promise().done(…) method call", + "tag": "JSONSummary" + }, + { + "span": { + "these": [ + { + "start": [ + 1, + 58 + ], + "name": "chained-property-access.js", + "end": [ + 1, + 66 + ] + }, + { + "start": [ + 1, + 60 + ], + "name": "chained-property-access.js", + "end": [ + 1, + 70 + ] + } + ] + }, + "summary": "Replaced the 'newDefer' identifier with the 'otherDefer' identifier in the returned.promise().done(…).fail(…) method call", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "chained-property-access.js" + ], + "sha1": "49366eb9b5adfc0372d1b58a87acd15c8052a606", + "gitDir": "test/corpus/repos/javascript", + "sha2": "301c255bc3e410697be6bb102e8b9e9d107666a0" +} +,{ + "testCaseDescription": "javascript-chained-property-access-delete-replacement-test", + "expectedResult": { + "changes": { + "chained-property-access.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "chained-property-access.js", + "end": [ + 2, + 1 + ] + } + }, + "summary": "Deleted the 'returned.promise().done(…).fail(…)' return statement", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 1 + ], + "name": "chained-property-access.js", + "end": [ + 3, + 1 + ] + } + }, + "summary": "Deleted the 'returned.promise().done(…).fail(…)' return statement", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "chained-property-access.js", + "end": [ + 3, + 1 + ] + } + }, + "summary": "Added the 'returned.promise().done(…).fail(…)' return statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "chained-property-access.js" + ], + "sha1": "301c255bc3e410697be6bb102e8b9e9d107666a0", + "gitDir": "test/corpus/repos/javascript", + "sha2": "49ea61cc98251e249f226f8787bbee08511fe9e9" +} +,{ + "testCaseDescription": "javascript-chained-property-access-delete-test", + "expectedResult": { + "changes": { + "chained-property-access.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "chained-property-access.js", + "end": [ + 2, + 1 + ] + } + }, + "summary": "Deleted the 'returned.promise().done(…).fail(…)' return statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "chained-property-access.js" + ], + "sha1": "49ea61cc98251e249f226f8787bbee08511fe9e9", + "gitDir": "test/corpus/repos/javascript", + "sha2": "8b1e3d552a64cdd2e542affda6527af005ebcb45" +} +,{ + "testCaseDescription": "javascript-chained-property-access-delete-rest-test", + "expectedResult": { + "changes": { + "chained-property-access.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "chained-property-access.js", + "end": [ + 2, + 1 + ] + } + }, + "summary": "Deleted the 'returned.promise().done(…).fail(…)' return statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "chained-property-access.js" + ], + "sha1": "8b1e3d552a64cdd2e542affda6527af005ebcb45", + "gitDir": "test/corpus/repos/javascript", + "sha2": "26f941c6191463416b1c6a56314b19dfe5d09221" +}] diff --git a/test/corpus/diff-summaries/javascript/class.json b/test/corpus/diff-summaries/javascript/class.json new file mode 100644 index 000000000..5adc5f1a1 --- /dev/null +++ b/test/corpus/diff-summaries/javascript/class.json @@ -0,0 +1,428 @@ +[{ + "testCaseDescription": "javascript-class-insert-test", + "expectedResult": { + "changes": { + "class.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "class.js", + "end": [ + 1, + 87 + ] + } + }, + "summary": "Added the 'Foo' class", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "class.js" + ], + "sha1": "3c4c5929ba3cb9bc23b211787745791de8774d2d", + "gitDir": "test/corpus/repos/javascript", + "sha2": "b728e40d8d1a035c46c62d3edc01f1e30d06bf59" +} +,{ + "testCaseDescription": "javascript-class-replacement-insert-test", + "expectedResult": { + "changes": { + "class.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "class.js", + "end": [ + 1, + 85 + ] + } + }, + "summary": "Added the 'Foo' class", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "class.js", + "end": [ + 2, + 87 + ] + } + }, + "summary": "Added the 'Foo' class", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "class.js" + ], + "sha1": "b728e40d8d1a035c46c62d3edc01f1e30d06bf59", + "gitDir": "test/corpus/repos/javascript", + "sha2": "e4a75438dfa8e247778fa6e8319ccc35fa9cdcb3" +} +,{ + "testCaseDescription": "javascript-class-delete-insert-test", + "expectedResult": { + "changes": { + "class.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 20 + ], + "name": "class.js", + "end": [ + 1, + 23 + ] + }, + { + "start": [ + 1, + 20 + ], + "name": "class.js", + "end": [ + 1, + 23 + ] + } + ] + }, + "summary": "Replaced the 'foo' identifier with the 'one' identifier in the one method of the 'Foo' class", + "tag": "JSONSummary" + }, + { + "span": { + "these": [ + { + "start": [ + 1, + 42 + ], + "name": "class.js", + "end": [ + 1, + 45 + ] + }, + { + "start": [ + 1, + 42 + ], + "name": "class.js", + "end": [ + 1, + 45 + ] + } + ] + }, + "summary": "Replaced the 'bar' identifier with the 'two' identifier in the two method of the 'Foo' class", + "tag": "JSONSummary" + }, + { + "span": { + "these": [ + { + "start": [ + 1, + 63 + ], + "name": "class.js", + "end": [ + 1, + 66 + ] + }, + { + "start": [ + 1, + 63 + ], + "name": "class.js", + "end": [ + 1, + 68 + ] + } + ] + }, + "summary": "Replaced the 'baz' identifier with the 'three' identifier in the three method of the 'Foo' class", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "class.js" + ], + "sha1": "e4a75438dfa8e247778fa6e8319ccc35fa9cdcb3", + "gitDir": "test/corpus/repos/javascript", + "sha2": "a2cd250b0659258473156b0ad3bad3d081b8f047" +} +,{ + "testCaseDescription": "javascript-class-replacement-test", + "expectedResult": { + "changes": { + "class.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 20 + ], + "name": "class.js", + "end": [ + 1, + 23 + ] + }, + { + "start": [ + 1, + 20 + ], + "name": "class.js", + "end": [ + 1, + 23 + ] + } + ] + }, + "summary": "Replaced the 'one' identifier with the 'foo' identifier in the foo method of the 'Foo' class", + "tag": "JSONSummary" + }, + { + "span": { + "these": [ + { + "start": [ + 1, + 42 + ], + "name": "class.js", + "end": [ + 1, + 45 + ] + }, + { + "start": [ + 1, + 42 + ], + "name": "class.js", + "end": [ + 1, + 45 + ] + } + ] + }, + "summary": "Replaced the 'two' identifier with the 'bar' identifier in the bar method of the 'Foo' class", + "tag": "JSONSummary" + }, + { + "span": { + "these": [ + { + "start": [ + 1, + 63 + ], + "name": "class.js", + "end": [ + 1, + 68 + ] + }, + { + "start": [ + 1, + 63 + ], + "name": "class.js", + "end": [ + 1, + 66 + ] + } + ] + }, + "summary": "Replaced the 'three' identifier with the 'baz' identifier in the baz method of the 'Foo' class", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "class.js" + ], + "sha1": "a2cd250b0659258473156b0ad3bad3d081b8f047", + "gitDir": "test/corpus/repos/javascript", + "sha2": "0558a17e26ea263027bc60b26ca6f9b40c923746" +} +,{ + "testCaseDescription": "javascript-class-delete-replacement-test", + "expectedResult": { + "changes": { + "class.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "class.js", + "end": [ + 1, + 85 + ] + } + }, + "summary": "Deleted the 'Foo' class", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 1 + ], + "name": "class.js", + "end": [ + 2, + 87 + ] + } + }, + "summary": "Deleted the 'Foo' class", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "class.js", + "end": [ + 2, + 85 + ] + } + }, + "summary": "Added the 'Foo' class", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "class.js" + ], + "sha1": "0558a17e26ea263027bc60b26ca6f9b40c923746", + "gitDir": "test/corpus/repos/javascript", + "sha2": "4247bf279aca71be7ae67e8853a46e56ecc1bcdc" +} +,{ + "testCaseDescription": "javascript-class-delete-test", + "expectedResult": { + "changes": { + "class.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "class.js", + "end": [ + 1, + 87 + ] + } + }, + "summary": "Deleted the 'Foo' class", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "class.js" + ], + "sha1": "4247bf279aca71be7ae67e8853a46e56ecc1bcdc", + "gitDir": "test/corpus/repos/javascript", + "sha2": "8724757eda59b1c3a89ac88298c706023d3480e5" +} +,{ + "testCaseDescription": "javascript-class-delete-rest-test", + "expectedResult": { + "changes": { + "class.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "class.js", + "end": [ + 1, + 85 + ] + } + }, + "summary": "Deleted the 'Foo' class", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "class.js" + ], + "sha1": "8724757eda59b1c3a89ac88298c706023d3480e5", + "gitDir": "test/corpus/repos/javascript", + "sha2": "6c3b6d5c7d426a657e90d97cdfd248b2453bc087" +}] diff --git a/test/corpus/diff-summaries/javascript/comma-operator.json b/test/corpus/diff-summaries/javascript/comma-operator.json new file mode 100644 index 000000000..3797a9341 --- /dev/null +++ b/test/corpus/diff-summaries/javascript/comma-operator.json @@ -0,0 +1,418 @@ +[{ + "testCaseDescription": "javascript-comma-operator-insert-test", + "expectedResult": { + "changes": { + "comma-operator.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "comma-operator.js", + "end": [ + 1, + 6 + ] + } + }, + "summary": "Added the 'a' assignment", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 1, + 8 + ], + "name": "comma-operator.js", + "end": [ + 1, + 13 + ] + } + }, + "summary": "Added the 'b' assignment", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "comma-operator.js" + ], + "sha1": "25e371a5c0ef7434f562af7ca9a9bfab5a157932", + "gitDir": "test/corpus/repos/javascript", + "sha2": "1c93fcbaca04d643a2ddeabe0b6e5d322df2a4fb" +} +,{ + "testCaseDescription": "javascript-comma-operator-replacement-insert-test", + "expectedResult": { + "changes": { + "comma-operator.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "comma-operator.js", + "end": [ + 1, + 23 + ] + } + }, + "summary": "Added the 'c' assignment", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "comma-operator.js", + "end": [ + 2, + 6 + ] + } + }, + "summary": "Added the 'a' assignment", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 8 + ], + "name": "comma-operator.js", + "end": [ + 2, + 13 + ] + } + }, + "summary": "Added the 'b' assignment", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "comma-operator.js" + ], + "sha1": "1c93fcbaca04d643a2ddeabe0b6e5d322df2a4fb", + "gitDir": "test/corpus/repos/javascript", + "sha2": "331db399698c11dfc5b4ff49f72b77e3910d5f01" +} +,{ + "testCaseDescription": "javascript-comma-operator-delete-insert-test", + "expectedResult": { + "changes": { + "comma-operator.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "comma-operator.js", + "end": [ + 1, + 6 + ] + } + }, + "summary": "Added the 'a' assignment", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 1, + 8 + ], + "name": "comma-operator.js", + "end": [ + 1, + 13 + ] + } + }, + "summary": "Added the 'b' assignment", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "comma-operator.js", + "end": [ + 1, + 23 + ] + } + }, + "summary": "Deleted the 'c' assignment", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "comma-operator.js" + ], + "sha1": "331db399698c11dfc5b4ff49f72b77e3910d5f01", + "gitDir": "test/corpus/repos/javascript", + "sha2": "d82e3a6dffefade301dbda072bf59931587b9196" +} +,{ + "testCaseDescription": "javascript-comma-operator-replacement-test", + "expectedResult": { + "changes": { + "comma-operator.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "comma-operator.js", + "end": [ + 1, + 23 + ] + } + }, + "summary": "Added the 'c' assignment", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "comma-operator.js", + "end": [ + 1, + 6 + ] + } + }, + "summary": "Deleted the 'a' assignment", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 1, + 8 + ], + "name": "comma-operator.js", + "end": [ + 1, + 13 + ] + } + }, + "summary": "Deleted the 'b' assignment", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "comma-operator.js" + ], + "sha1": "d82e3a6dffefade301dbda072bf59931587b9196", + "gitDir": "test/corpus/repos/javascript", + "sha2": "bcb931f34cdfe5d7f167afd79d1d1196284f9587" +} +,{ + "testCaseDescription": "javascript-comma-operator-delete-replacement-test", + "expectedResult": { + "changes": { + "comma-operator.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "comma-operator.js", + "end": [ + 1, + 23 + ] + } + }, + "summary": "Deleted the 'c' assignment", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 1 + ], + "name": "comma-operator.js", + "end": [ + 2, + 6 + ] + } + }, + "summary": "Deleted the 'a' assignment", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 8 + ], + "name": "comma-operator.js", + "end": [ + 2, + 13 + ] + } + }, + "summary": "Deleted the 'b' assignment", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "comma-operator.js", + "end": [ + 2, + 23 + ] + } + }, + "summary": "Added the 'c' assignment", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "comma-operator.js" + ], + "sha1": "bcb931f34cdfe5d7f167afd79d1d1196284f9587", + "gitDir": "test/corpus/repos/javascript", + "sha2": "59f0b3ae2045827b2be7200f3ae10d13daef566e" +} +,{ + "testCaseDescription": "javascript-comma-operator-delete-test", + "expectedResult": { + "changes": { + "comma-operator.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "comma-operator.js", + "end": [ + 1, + 6 + ] + } + }, + "summary": "Deleted the 'a' assignment", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 1, + 8 + ], + "name": "comma-operator.js", + "end": [ + 1, + 13 + ] + } + }, + "summary": "Deleted the 'b' assignment", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "comma-operator.js" + ], + "sha1": "59f0b3ae2045827b2be7200f3ae10d13daef566e", + "gitDir": "test/corpus/repos/javascript", + "sha2": "8f59d35152aa46577234e3fd8c00122b9182574d" +} +,{ + "testCaseDescription": "javascript-comma-operator-delete-rest-test", + "expectedResult": { + "changes": { + "comma-operator.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "comma-operator.js", + "end": [ + 1, + 23 + ] + } + }, + "summary": "Deleted the 'c' assignment", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "comma-operator.js" + ], + "sha1": "8f59d35152aa46577234e3fd8c00122b9182574d", + "gitDir": "test/corpus/repos/javascript", + "sha2": "7086396295d14f41207e8fbae4d350f2672a77dd" +}] diff --git a/test/corpus/diff-summaries/javascript/comment.json b/test/corpus/diff-summaries/javascript/comment.json new file mode 100644 index 000000000..2c147d961 --- /dev/null +++ b/test/corpus/diff-summaries/javascript/comment.json @@ -0,0 +1,308 @@ +[{ + "testCaseDescription": "javascript-comment-insert-test", + "expectedResult": { + "changes": { + "comment.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "comment.js", + "end": [ + 1, + 22 + ] + } + }, + "summary": "Added the '// This is a property' comment", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "comment.js" + ], + "sha1": "a67c36dee6afa77efd8005ab23227f683239d35e", + "gitDir": "test/corpus/repos/javascript", + "sha2": "7d283c6fbe1d5b29e2ab629ee8d18e668b206e80" +} +,{ + "testCaseDescription": "javascript-comment-replacement-insert-test", + "expectedResult": { + "changes": { + "comment.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "comment.js", + "end": [ + 3, + 3 + ] + } + }, + "summary": "Added the '/*\n * This is a method\n*/' comment", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 4, + 1 + ], + "name": "comment.js", + "end": [ + 4, + 22 + ] + } + }, + "summary": "Added the '// This is a property' comment", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "comment.js" + ], + "sha1": "7d283c6fbe1d5b29e2ab629ee8d18e668b206e80", + "gitDir": "test/corpus/repos/javascript", + "sha2": "7368c3a098046a807d136e1e86467f6c2b6ec81a" +} +,{ + "testCaseDescription": "javascript-comment-delete-insert-test", + "expectedResult": { + "changes": { + "comment.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 1 + ], + "name": "comment.js", + "end": [ + 3, + 3 + ] + }, + { + "start": [ + 1, + 1 + ], + "name": "comment.js", + "end": [ + 1, + 22 + ] + } + ] + }, + "summary": "Replaced the '/*\n * This is a method\n*/' comment with the '// This is a property' comment", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "comment.js" + ], + "sha1": "7368c3a098046a807d136e1e86467f6c2b6ec81a", + "gitDir": "test/corpus/repos/javascript", + "sha2": "1cf6f98c7f88af7a9a75863c4fd38202308014ea" +} +,{ + "testCaseDescription": "javascript-comment-replacement-test", + "expectedResult": { + "changes": { + "comment.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 1 + ], + "name": "comment.js", + "end": [ + 1, + 22 + ] + }, + { + "start": [ + 1, + 1 + ], + "name": "comment.js", + "end": [ + 3, + 3 + ] + } + ] + }, + "summary": "Replaced the '// This is a property' comment with the '/*\n * This is a method\n*/' comment", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "comment.js" + ], + "sha1": "1cf6f98c7f88af7a9a75863c4fd38202308014ea", + "gitDir": "test/corpus/repos/javascript", + "sha2": "aafd41680947235874cd0070f3970a712f140f79" +} +,{ + "testCaseDescription": "javascript-comment-delete-replacement-test", + "expectedResult": { + "changes": { + "comment.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "comment.js", + "end": [ + 3, + 3 + ] + } + }, + "summary": "Deleted the '/*\n * This is a method\n*/' comment", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 4, + 1 + ], + "name": "comment.js", + "end": [ + 4, + 22 + ] + } + }, + "summary": "Deleted the '// This is a property' comment", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "comment.js", + "end": [ + 4, + 3 + ] + } + }, + "summary": "Added the '/*\n * This is a method\n*/' comment", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "comment.js" + ], + "sha1": "aafd41680947235874cd0070f3970a712f140f79", + "gitDir": "test/corpus/repos/javascript", + "sha2": "6b6457fbd3a6977f7041f32f5cbb59d86f82853a" +} +,{ + "testCaseDescription": "javascript-comment-delete-test", + "expectedResult": { + "changes": { + "comment.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "comment.js", + "end": [ + 1, + 22 + ] + } + }, + "summary": "Deleted the '// This is a property' comment", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "comment.js" + ], + "sha1": "6b6457fbd3a6977f7041f32f5cbb59d86f82853a", + "gitDir": "test/corpus/repos/javascript", + "sha2": "1f1632420d5cb8f7794652942c29badb4b2ea481" +} +,{ + "testCaseDescription": "javascript-comment-delete-rest-test", + "expectedResult": { + "changes": { + "comment.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "comment.js", + "end": [ + 3, + 3 + ] + } + }, + "summary": "Deleted the '/*\n * This is a method\n*/' comment", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "comment.js" + ], + "sha1": "1f1632420d5cb8f7794652942c29badb4b2ea481", + "gitDir": "test/corpus/repos/javascript", + "sha2": "9edcc470495aad2ae2b395a18179ec07829ad591" +}] diff --git a/test/corpus/diff-summaries/javascript/constructor-call.json b/test/corpus/diff-summaries/javascript/constructor-call.json new file mode 100644 index 000000000..abc18dedb --- /dev/null +++ b/test/corpus/diff-summaries/javascript/constructor-call.json @@ -0,0 +1,308 @@ +[{ + "testCaseDescription": "javascript-constructor-call-insert-test", + "expectedResult": { + "changes": { + "constructor-call.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "constructor-call.js", + "end": [ + 1, + 27 + ] + } + }, + "summary": "Added the 'module.Klass(1, \"two\")' constructor", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "constructor-call.js" + ], + "sha1": "e67227e82c01378ae1102d7579e52a47e06ef16a", + "gitDir": "test/corpus/repos/javascript", + "sha2": "86912d55ecac17b3ce2c8370e06b361daa72a63d" +} +,{ + "testCaseDescription": "javascript-constructor-call-replacement-insert-test", + "expectedResult": { + "changes": { + "constructor-call.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "constructor-call.js", + "end": [ + 1, + 29 + ] + } + }, + "summary": "Added the 'module.Klass(1, \"three\")' constructor", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "constructor-call.js", + "end": [ + 2, + 27 + ] + } + }, + "summary": "Added the 'module.Klass(1, \"two\")' constructor", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "constructor-call.js" + ], + "sha1": "86912d55ecac17b3ce2c8370e06b361daa72a63d", + "gitDir": "test/corpus/repos/javascript", + "sha2": "eec1530d637fa82ada4aaf549e576f8f4530b458" +} +,{ + "testCaseDescription": "javascript-constructor-call-delete-insert-test", + "expectedResult": { + "changes": { + "constructor-call.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 21 + ], + "name": "constructor-call.js", + "end": [ + 1, + 28 + ] + }, + { + "start": [ + 1, + 21 + ], + "name": "constructor-call.js", + "end": [ + 1, + 26 + ] + } + ] + }, + "summary": "Replaced the \"three\" string with the \"two\" string in the module.Klass(1, \"two\") method call", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "constructor-call.js" + ], + "sha1": "eec1530d637fa82ada4aaf549e576f8f4530b458", + "gitDir": "test/corpus/repos/javascript", + "sha2": "6823bb31a08af05908b3276127c191d5bdfd89b6" +} +,{ + "testCaseDescription": "javascript-constructor-call-replacement-test", + "expectedResult": { + "changes": { + "constructor-call.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 21 + ], + "name": "constructor-call.js", + "end": [ + 1, + 26 + ] + }, + { + "start": [ + 1, + 21 + ], + "name": "constructor-call.js", + "end": [ + 1, + 28 + ] + } + ] + }, + "summary": "Replaced the \"two\" string with the \"three\" string in the module.Klass(1, \"three\") method call", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "constructor-call.js" + ], + "sha1": "6823bb31a08af05908b3276127c191d5bdfd89b6", + "gitDir": "test/corpus/repos/javascript", + "sha2": "0d42b2f3722e4f1bd33f10099a2b9b92368ea62e" +} +,{ + "testCaseDescription": "javascript-constructor-call-delete-replacement-test", + "expectedResult": { + "changes": { + "constructor-call.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "constructor-call.js", + "end": [ + 1, + 29 + ] + } + }, + "summary": "Deleted the 'module.Klass(1, \"three\")' constructor", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 1 + ], + "name": "constructor-call.js", + "end": [ + 2, + 27 + ] + } + }, + "summary": "Deleted the 'module.Klass(1, \"two\")' constructor", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "constructor-call.js", + "end": [ + 2, + 29 + ] + } + }, + "summary": "Added the 'module.Klass(1, \"three\")' constructor", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "constructor-call.js" + ], + "sha1": "0d42b2f3722e4f1bd33f10099a2b9b92368ea62e", + "gitDir": "test/corpus/repos/javascript", + "sha2": "b17ad17aa14e02fd6c5a6593e7c9e1b6be2ace5d" +} +,{ + "testCaseDescription": "javascript-constructor-call-delete-test", + "expectedResult": { + "changes": { + "constructor-call.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "constructor-call.js", + "end": [ + 1, + 27 + ] + } + }, + "summary": "Deleted the 'module.Klass(1, \"two\")' constructor", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "constructor-call.js" + ], + "sha1": "b17ad17aa14e02fd6c5a6593e7c9e1b6be2ace5d", + "gitDir": "test/corpus/repos/javascript", + "sha2": "c228196872cbf218531b4e3bd82250e2bce507da" +} +,{ + "testCaseDescription": "javascript-constructor-call-delete-rest-test", + "expectedResult": { + "changes": { + "constructor-call.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "constructor-call.js", + "end": [ + 1, + 29 + ] + } + }, + "summary": "Deleted the 'module.Klass(1, \"three\")' constructor", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "constructor-call.js" + ], + "sha1": "c228196872cbf218531b4e3bd82250e2bce507da", + "gitDir": "test/corpus/repos/javascript", + "sha2": "31ae73e147d1cd8cf95cfdf871344f18fdc91fa2" +}] diff --git a/test/corpus/diff-summaries/javascript/delete-operator.json b/test/corpus/diff-summaries/javascript/delete-operator.json new file mode 100644 index 000000000..c20d2f6be --- /dev/null +++ b/test/corpus/diff-summaries/javascript/delete-operator.json @@ -0,0 +1,308 @@ +[{ + "testCaseDescription": "javascript-delete-operator-insert-test", + "expectedResult": { + "changes": { + "delete-operator.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "delete-operator.js", + "end": [ + 1, + 21 + ] + } + }, + "summary": "Added the 'delete thing['prop']' operator", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "delete-operator.js" + ], + "sha1": "c012557afb55395556a9209537f977c480c9cfa2", + "gitDir": "test/corpus/repos/javascript", + "sha2": "6b1159e64aeea120283214debcf6b90846dd2d25" +} +,{ + "testCaseDescription": "javascript-delete-operator-replacement-insert-test", + "expectedResult": { + "changes": { + "delete-operator.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "delete-operator.js", + "end": [ + 1, + 18 + ] + } + }, + "summary": "Added the 'delete thing.prop' operator", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "delete-operator.js", + "end": [ + 2, + 21 + ] + } + }, + "summary": "Added the 'delete thing['prop']' operator", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "delete-operator.js" + ], + "sha1": "6b1159e64aeea120283214debcf6b90846dd2d25", + "gitDir": "test/corpus/repos/javascript", + "sha2": "30def9e5c20b4b581b85c5fa83ce538254f9cf92" +} +,{ + "testCaseDescription": "javascript-delete-operator-delete-insert-test", + "expectedResult": { + "changes": { + "delete-operator.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 1 + ], + "name": "delete-operator.js", + "end": [ + 1, + 18 + ] + }, + { + "start": [ + 1, + 1 + ], + "name": "delete-operator.js", + "end": [ + 1, + 21 + ] + } + ] + }, + "summary": "Replaced the 'delete thing.prop' operator with the 'delete thing['prop']' operator", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "delete-operator.js" + ], + "sha1": "30def9e5c20b4b581b85c5fa83ce538254f9cf92", + "gitDir": "test/corpus/repos/javascript", + "sha2": "f5f742849965b8ac6d6ddac053ae7ad8638d3f56" +} +,{ + "testCaseDescription": "javascript-delete-operator-replacement-test", + "expectedResult": { + "changes": { + "delete-operator.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 1 + ], + "name": "delete-operator.js", + "end": [ + 1, + 21 + ] + }, + { + "start": [ + 1, + 1 + ], + "name": "delete-operator.js", + "end": [ + 1, + 18 + ] + } + ] + }, + "summary": "Replaced the 'delete thing['prop']' operator with the 'delete thing.prop' operator", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "delete-operator.js" + ], + "sha1": "f5f742849965b8ac6d6ddac053ae7ad8638d3f56", + "gitDir": "test/corpus/repos/javascript", + "sha2": "28436cc38cd7b95a4f00bb6764bb77f5d7ae3e63" +} +,{ + "testCaseDescription": "javascript-delete-operator-delete-replacement-test", + "expectedResult": { + "changes": { + "delete-operator.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "delete-operator.js", + "end": [ + 1, + 18 + ] + } + }, + "summary": "Deleted the 'delete thing.prop' operator", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 1 + ], + "name": "delete-operator.js", + "end": [ + 2, + 21 + ] + } + }, + "summary": "Deleted the 'delete thing['prop']' operator", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "delete-operator.js", + "end": [ + 2, + 18 + ] + } + }, + "summary": "Added the 'delete thing.prop' operator", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "delete-operator.js" + ], + "sha1": "28436cc38cd7b95a4f00bb6764bb77f5d7ae3e63", + "gitDir": "test/corpus/repos/javascript", + "sha2": "24b9fc05822bbc3b202fbe797de7daab301bf045" +} +,{ + "testCaseDescription": "javascript-delete-operator-delete-test", + "expectedResult": { + "changes": { + "delete-operator.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "delete-operator.js", + "end": [ + 1, + 21 + ] + } + }, + "summary": "Deleted the 'delete thing['prop']' operator", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "delete-operator.js" + ], + "sha1": "24b9fc05822bbc3b202fbe797de7daab301bf045", + "gitDir": "test/corpus/repos/javascript", + "sha2": "16b0f30eb7f79f324a914ab14940e3ebb1e0f376" +} +,{ + "testCaseDescription": "javascript-delete-operator-delete-rest-test", + "expectedResult": { + "changes": { + "delete-operator.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "delete-operator.js", + "end": [ + 1, + 18 + ] + } + }, + "summary": "Deleted the 'delete thing.prop' operator", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "delete-operator.js" + ], + "sha1": "16b0f30eb7f79f324a914ab14940e3ebb1e0f376", + "gitDir": "test/corpus/repos/javascript", + "sha2": "4c9359461db3f23921b2af834190b8c9966fa455" +}] diff --git a/test/corpus/diff-summaries/javascript/do-while-statement.json b/test/corpus/diff-summaries/javascript/do-while-statement.json new file mode 100644 index 000000000..077225210 --- /dev/null +++ b/test/corpus/diff-summaries/javascript/do-while-statement.json @@ -0,0 +1,368 @@ +[{ + "testCaseDescription": "javascript-do-while-statement-insert-test", + "expectedResult": { + "changes": { + "do-while-statement.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "do-while-statement.js", + "end": [ + 1, + 42 + ] + } + }, + "summary": "Added the 'true' do/while statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "do-while-statement.js" + ], + "sha1": "2991c8cdbe1144d3164c0fc0075cb5388e06583b", + "gitDir": "test/corpus/repos/javascript", + "sha2": "fc1fd9e059e6088b851598dc684d5408adbf0168" +} +,{ + "testCaseDescription": "javascript-do-while-statement-replacement-insert-test", + "expectedResult": { + "changes": { + "do-while-statement.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "do-while-statement.js", + "end": [ + 1, + 48 + ] + } + }, + "summary": "Added the 'false' do/while statement", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "do-while-statement.js", + "end": [ + 2, + 42 + ] + } + }, + "summary": "Added the 'true' do/while statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "do-while-statement.js" + ], + "sha1": "fc1fd9e059e6088b851598dc684d5408adbf0168", + "gitDir": "test/corpus/repos/javascript", + "sha2": "324526a23b5490a9859a781516afa5e58a66d774" +} +,{ + "testCaseDescription": "javascript-do-while-statement-delete-insert-test", + "expectedResult": { + "changes": { + "do-while-statement.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 18 + ], + "name": "do-while-statement.js", + "end": [ + 1, + 29 + ] + }, + { + "start": [ + 1, + 18 + ], + "name": "do-while-statement.js", + "end": [ + 1, + 24 + ] + } + ] + }, + "summary": "Replaced the 'replacement' identifier with the 'insert' identifier in the console.log(insert) method call", + "tag": "JSONSummary" + }, + { + "span": { + "these": [ + { + "start": [ + 1, + 41 + ], + "name": "do-while-statement.js", + "end": [ + 1, + 46 + ] + }, + { + "start": [ + 1, + 36 + ], + "name": "do-while-statement.js", + "end": [ + 1, + 40 + ] + } + ] + }, + "summary": "Replaced 'false' with 'true' in the true do/while statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "do-while-statement.js" + ], + "sha1": "324526a23b5490a9859a781516afa5e58a66d774", + "gitDir": "test/corpus/repos/javascript", + "sha2": "6163229e116d6f51f04f0865b21705630e6e4329" +} +,{ + "testCaseDescription": "javascript-do-while-statement-replacement-test", + "expectedResult": { + "changes": { + "do-while-statement.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 18 + ], + "name": "do-while-statement.js", + "end": [ + 1, + 24 + ] + }, + { + "start": [ + 1, + 18 + ], + "name": "do-while-statement.js", + "end": [ + 1, + 29 + ] + } + ] + }, + "summary": "Replaced the 'insert' identifier with the 'replacement' identifier in the console.log(replacement) method call", + "tag": "JSONSummary" + }, + { + "span": { + "these": [ + { + "start": [ + 1, + 36 + ], + "name": "do-while-statement.js", + "end": [ + 1, + 40 + ] + }, + { + "start": [ + 1, + 41 + ], + "name": "do-while-statement.js", + "end": [ + 1, + 46 + ] + } + ] + }, + "summary": "Replaced 'true' with 'false' in the false do/while statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "do-while-statement.js" + ], + "sha1": "6163229e116d6f51f04f0865b21705630e6e4329", + "gitDir": "test/corpus/repos/javascript", + "sha2": "6cfc9a2d6fdbcd14d80a9519e5c9e3d66092950e" +} +,{ + "testCaseDescription": "javascript-do-while-statement-delete-replacement-test", + "expectedResult": { + "changes": { + "do-while-statement.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "do-while-statement.js", + "end": [ + 1, + 48 + ] + } + }, + "summary": "Deleted the 'false' do/while statement", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 1 + ], + "name": "do-while-statement.js", + "end": [ + 2, + 42 + ] + } + }, + "summary": "Deleted the 'true' do/while statement", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "do-while-statement.js", + "end": [ + 2, + 48 + ] + } + }, + "summary": "Added the 'false' do/while statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "do-while-statement.js" + ], + "sha1": "6cfc9a2d6fdbcd14d80a9519e5c9e3d66092950e", + "gitDir": "test/corpus/repos/javascript", + "sha2": "9b5e3c1beb3f77b171aa0d6fcf01af966d96978a" +} +,{ + "testCaseDescription": "javascript-do-while-statement-delete-test", + "expectedResult": { + "changes": { + "do-while-statement.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "do-while-statement.js", + "end": [ + 1, + 42 + ] + } + }, + "summary": "Deleted the 'true' do/while statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "do-while-statement.js" + ], + "sha1": "9b5e3c1beb3f77b171aa0d6fcf01af966d96978a", + "gitDir": "test/corpus/repos/javascript", + "sha2": "b4a3e1ab3c7306658c103f007c53334d8b27783c" +} +,{ + "testCaseDescription": "javascript-do-while-statement-delete-rest-test", + "expectedResult": { + "changes": { + "do-while-statement.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "do-while-statement.js", + "end": [ + 1, + 48 + ] + } + }, + "summary": "Deleted the 'false' do/while statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "do-while-statement.js" + ], + "sha1": "b4a3e1ab3c7306658c103f007c53334d8b27783c", + "gitDir": "test/corpus/repos/javascript", + "sha2": "11ce49dc14d6c3b4c0baef54a2456d4bc667b992" +}] diff --git a/test/corpus/diff-summaries/javascript/false.json b/test/corpus/diff-summaries/javascript/false.json new file mode 100644 index 000000000..4ef6357b4 --- /dev/null +++ b/test/corpus/diff-summaries/javascript/false.json @@ -0,0 +1,316 @@ +[{ + "testCaseDescription": "javascript-false-insert-test", + "expectedResult": { + "changes": { + "false.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "false.js", + "end": [ + 1, + 6 + ] + } + }, + "summary": "Added 'false'", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "false.js" + ], + "sha1": "9c5eadaa5e35756fff0d96ba9830a7e0dbf30fd7", + "gitDir": "test/corpus/repos/javascript", + "sha2": "9d32877cdcecf69747e88be24da7b721a64d27ac" +} +,{ + "testCaseDescription": "javascript-false-replacement-insert-test", + "expectedResult": { + "changes": { + "false.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "false.js", + "end": [ + 1, + 14 + ] + } + }, + "summary": "Added the 'false' return statement", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "false.js", + "end": [ + 2, + 6 + ] + } + }, + "summary": "Added 'false'", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "false.js" + ], + "sha1": "9d32877cdcecf69747e88be24da7b721a64d27ac", + "gitDir": "test/corpus/repos/javascript", + "sha2": "4e71c4594699213f53e0b4a77b2623b6f8494ace" +} +,{ + "testCaseDescription": "javascript-false-delete-insert-test", + "expectedResult": { + "changes": { + "false.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "false.js", + "end": [ + 1, + 6 + ] + } + }, + "summary": "Added 'false'", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "false.js", + "end": [ + 1, + 14 + ] + } + }, + "summary": "Deleted the 'false' return statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "false.js" + ], + "sha1": "4e71c4594699213f53e0b4a77b2623b6f8494ace", + "gitDir": "test/corpus/repos/javascript", + "sha2": "b048ef1312ed02ee53c84180a16525a67ad70242" +} +,{ + "testCaseDescription": "javascript-false-replacement-test", + "expectedResult": { + "changes": { + "false.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "false.js", + "end": [ + 1, + 14 + ] + } + }, + "summary": "Added the 'false' return statement", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "false.js", + "end": [ + 1, + 6 + ] + } + }, + "summary": "Deleted 'false'", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "false.js" + ], + "sha1": "b048ef1312ed02ee53c84180a16525a67ad70242", + "gitDir": "test/corpus/repos/javascript", + "sha2": "15d1111d0020c65e3fca9491cb735534fb26e5a9" +} +,{ + "testCaseDescription": "javascript-false-delete-replacement-test", + "expectedResult": { + "changes": { + "false.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "false.js", + "end": [ + 1, + 14 + ] + } + }, + "summary": "Deleted the 'false' return statement", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 1 + ], + "name": "false.js", + "end": [ + 2, + 6 + ] + } + }, + "summary": "Deleted 'false'", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "false.js", + "end": [ + 2, + 14 + ] + } + }, + "summary": "Added the 'false' return statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "false.js" + ], + "sha1": "15d1111d0020c65e3fca9491cb735534fb26e5a9", + "gitDir": "test/corpus/repos/javascript", + "sha2": "15884b8d34208b933c4319248220797995363a4c" +} +,{ + "testCaseDescription": "javascript-false-delete-test", + "expectedResult": { + "changes": { + "false.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "false.js", + "end": [ + 1, + 6 + ] + } + }, + "summary": "Deleted 'false'", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "false.js" + ], + "sha1": "15884b8d34208b933c4319248220797995363a4c", + "gitDir": "test/corpus/repos/javascript", + "sha2": "a85e48b940d5259b7690df8c59df1a5bb6052d16" +} +,{ + "testCaseDescription": "javascript-false-delete-rest-test", + "expectedResult": { + "changes": { + "false.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "false.js", + "end": [ + 1, + 14 + ] + } + }, + "summary": "Deleted the 'false' return statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "false.js" + ], + "sha1": "a85e48b940d5259b7690df8c59df1a5bb6052d16", + "gitDir": "test/corpus/repos/javascript", + "sha2": "3c4c5929ba3cb9bc23b211787745791de8774d2d" +}] diff --git a/test/corpus/diff-summaries/javascript/for-in-statement.json b/test/corpus/diff-summaries/javascript/for-in-statement.json new file mode 100644 index 000000000..d1b9b6708 --- /dev/null +++ b/test/corpus/diff-summaries/javascript/for-in-statement.json @@ -0,0 +1,428 @@ +[{ + "testCaseDescription": "javascript-for-in-statement-insert-test", + "expectedResult": { + "changes": { + "for-in-statement.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "for-in-statement.js", + "end": [ + 1, + 35 + ] + } + }, + "summary": "Added the 'thing in things' for statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "for-in-statement.js" + ], + "sha1": "215eb7570ac9ccb686598ee7a6c1ddc9c0562224", + "gitDir": "test/corpus/repos/javascript", + "sha2": "a2be2a6bc55d7d2613d647e725e39fe79fd1ca21" +} +,{ + "testCaseDescription": "javascript-for-in-statement-replacement-insert-test", + "expectedResult": { + "changes": { + "for-in-statement.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "for-in-statement.js", + "end": [ + 1, + 32 + ] + } + }, + "summary": "Added the 'item in items' for statement", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "for-in-statement.js", + "end": [ + 2, + 35 + ] + } + }, + "summary": "Added the 'thing in things' for statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "for-in-statement.js" + ], + "sha1": "a2be2a6bc55d7d2613d647e725e39fe79fd1ca21", + "gitDir": "test/corpus/repos/javascript", + "sha2": "aa607b9e541223522cd47ab5d98b1289df8033db" +} +,{ + "testCaseDescription": "javascript-for-in-statement-delete-insert-test", + "expectedResult": { + "changes": { + "for-in-statement.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 6 + ], + "name": "for-in-statement.js", + "end": [ + 1, + 10 + ] + }, + { + "start": [ + 1, + 6 + ], + "name": "for-in-statement.js", + "end": [ + 1, + 11 + ] + } + ] + }, + "summary": "Replaced the 'item' identifier with the 'thing' identifier", + "tag": "JSONSummary" + }, + { + "span": { + "these": [ + { + "start": [ + 1, + 14 + ], + "name": "for-in-statement.js", + "end": [ + 1, + 19 + ] + }, + { + "start": [ + 1, + 15 + ], + "name": "for-in-statement.js", + "end": [ + 1, + 21 + ] + } + ] + }, + "summary": "Replaced the 'items' identifier with the 'things' identifier", + "tag": "JSONSummary" + }, + { + "span": { + "these": [ + { + "start": [ + 1, + 23 + ], + "name": "for-in-statement.js", + "end": [ + 1, + 27 + ] + }, + { + "start": [ + 1, + 25 + ], + "name": "for-in-statement.js", + "end": [ + 1, + 30 + ] + } + ] + }, + "summary": "Replaced the 'item' identifier with the 'thing' identifier in the thing() function call", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "for-in-statement.js" + ], + "sha1": "aa607b9e541223522cd47ab5d98b1289df8033db", + "gitDir": "test/corpus/repos/javascript", + "sha2": "eaa14214e9d18894bf7f44347a1edc4a95966930" +} +,{ + "testCaseDescription": "javascript-for-in-statement-replacement-test", + "expectedResult": { + "changes": { + "for-in-statement.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 6 + ], + "name": "for-in-statement.js", + "end": [ + 1, + 11 + ] + }, + { + "start": [ + 1, + 6 + ], + "name": "for-in-statement.js", + "end": [ + 1, + 10 + ] + } + ] + }, + "summary": "Replaced the 'thing' identifier with the 'item' identifier", + "tag": "JSONSummary" + }, + { + "span": { + "these": [ + { + "start": [ + 1, + 15 + ], + "name": "for-in-statement.js", + "end": [ + 1, + 21 + ] + }, + { + "start": [ + 1, + 14 + ], + "name": "for-in-statement.js", + "end": [ + 1, + 19 + ] + } + ] + }, + "summary": "Replaced the 'things' identifier with the 'items' identifier", + "tag": "JSONSummary" + }, + { + "span": { + "these": [ + { + "start": [ + 1, + 25 + ], + "name": "for-in-statement.js", + "end": [ + 1, + 30 + ] + }, + { + "start": [ + 1, + 23 + ], + "name": "for-in-statement.js", + "end": [ + 1, + 27 + ] + } + ] + }, + "summary": "Replaced the 'thing' identifier with the 'item' identifier in the item() function call", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "for-in-statement.js" + ], + "sha1": "eaa14214e9d18894bf7f44347a1edc4a95966930", + "gitDir": "test/corpus/repos/javascript", + "sha2": "6007528cd72aa56e2f887a611c1b30ab2d922894" +} +,{ + "testCaseDescription": "javascript-for-in-statement-delete-replacement-test", + "expectedResult": { + "changes": { + "for-in-statement.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "for-in-statement.js", + "end": [ + 1, + 32 + ] + } + }, + "summary": "Deleted the 'item in items' for statement", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 1 + ], + "name": "for-in-statement.js", + "end": [ + 2, + 35 + ] + } + }, + "summary": "Deleted the 'thing in things' for statement", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "for-in-statement.js", + "end": [ + 2, + 32 + ] + } + }, + "summary": "Added the 'item in items' for statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "for-in-statement.js" + ], + "sha1": "6007528cd72aa56e2f887a611c1b30ab2d922894", + "gitDir": "test/corpus/repos/javascript", + "sha2": "9055c5f91ede476dde3667d3beabfc9e6ec1aa10" +} +,{ + "testCaseDescription": "javascript-for-in-statement-delete-test", + "expectedResult": { + "changes": { + "for-in-statement.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "for-in-statement.js", + "end": [ + 1, + 35 + ] + } + }, + "summary": "Deleted the 'thing in things' for statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "for-in-statement.js" + ], + "sha1": "9055c5f91ede476dde3667d3beabfc9e6ec1aa10", + "gitDir": "test/corpus/repos/javascript", + "sha2": "735ef2f75ff02bc497757685245f4fdc59422392" +} +,{ + "testCaseDescription": "javascript-for-in-statement-delete-rest-test", + "expectedResult": { + "changes": { + "for-in-statement.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "for-in-statement.js", + "end": [ + 1, + 32 + ] + } + }, + "summary": "Deleted the 'item in items' for statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "for-in-statement.js" + ], + "sha1": "735ef2f75ff02bc497757685245f4fdc59422392", + "gitDir": "test/corpus/repos/javascript", + "sha2": "1ad3455503bfb6621a6b418f015349c2bd2a957d" +}] diff --git a/test/corpus/diff-summaries/javascript/for-loop-with-in-statement.json b/test/corpus/diff-summaries/javascript/for-loop-with-in-statement.json new file mode 100644 index 000000000..6c104b60f --- /dev/null +++ b/test/corpus/diff-summaries/javascript/for-loop-with-in-statement.json @@ -0,0 +1,368 @@ +[{ + "testCaseDescription": "javascript-for-loop-with-in-statement-insert-test", + "expectedResult": { + "changes": { + "for-loop-with-in-statement.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "for-loop-with-in-statement.js", + "end": [ + 1, + 63 + ] + } + }, + "summary": "Added the 'key in something && i = 0; i < n; i++' for statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "for-loop-with-in-statement.js" + ], + "sha1": "1b5320f27fdf477cf7624573d5a594035788a73a", + "gitDir": "test/corpus/repos/javascript", + "sha2": "55e3c4b83a742572f51eea0548a8c0e3765fab29" +} +,{ + "testCaseDescription": "javascript-for-loop-with-in-statement-replacement-insert-test", + "expectedResult": { + "changes": { + "for-loop-with-in-statement.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "for-loop-with-in-statement.js", + "end": [ + 1, + 73 + ] + } + }, + "summary": "Added the 'otherKey in something && i = 0; i < n; i++' for statement", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "for-loop-with-in-statement.js", + "end": [ + 2, + 63 + ] + } + }, + "summary": "Added the 'key in something && i = 0; i < n; i++' for statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "for-loop-with-in-statement.js" + ], + "sha1": "55e3c4b83a742572f51eea0548a8c0e3765fab29", + "gitDir": "test/corpus/repos/javascript", + "sha2": "7fddb9aa46f4597ac5990bbb7ca0ef6d387030e3" +} +,{ + "testCaseDescription": "javascript-for-loop-with-in-statement-delete-insert-test", + "expectedResult": { + "changes": { + "for-loop-with-in-statement.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 6 + ], + "name": "for-loop-with-in-statement.js", + "end": [ + 1, + 14 + ] + }, + { + "start": [ + 1, + 6 + ], + "name": "for-loop-with-in-statement.js", + "end": [ + 1, + 9 + ] + } + ] + }, + "summary": "Replaced the 'otherKey' identifier with the 'key' identifier", + "tag": "JSONSummary" + }, + { + "span": { + "these": [ + { + "start": [ + 1, + 52 + ], + "name": "for-loop-with-in-statement.js", + "end": [ + 1, + 68 + ] + }, + { + "start": [ + 1, + 47 + ], + "name": "for-loop-with-in-statement.js", + "end": [ + 1, + 58 + ] + } + ] + }, + "summary": "Replaced the 'doOtherSomething' identifier with the 'doSomething' identifier in the doSomething() function call", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "for-loop-with-in-statement.js" + ], + "sha1": "7fddb9aa46f4597ac5990bbb7ca0ef6d387030e3", + "gitDir": "test/corpus/repos/javascript", + "sha2": "75afe5fde93638685d3adcc62ef9873c3d205763" +} +,{ + "testCaseDescription": "javascript-for-loop-with-in-statement-replacement-test", + "expectedResult": { + "changes": { + "for-loop-with-in-statement.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 6 + ], + "name": "for-loop-with-in-statement.js", + "end": [ + 1, + 9 + ] + }, + { + "start": [ + 1, + 6 + ], + "name": "for-loop-with-in-statement.js", + "end": [ + 1, + 14 + ] + } + ] + }, + "summary": "Replaced the 'key' identifier with the 'otherKey' identifier", + "tag": "JSONSummary" + }, + { + "span": { + "these": [ + { + "start": [ + 1, + 47 + ], + "name": "for-loop-with-in-statement.js", + "end": [ + 1, + 58 + ] + }, + { + "start": [ + 1, + 52 + ], + "name": "for-loop-with-in-statement.js", + "end": [ + 1, + 68 + ] + } + ] + }, + "summary": "Replaced the 'doSomething' identifier with the 'doOtherSomething' identifier in the doOtherSomething() function call", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "for-loop-with-in-statement.js" + ], + "sha1": "75afe5fde93638685d3adcc62ef9873c3d205763", + "gitDir": "test/corpus/repos/javascript", + "sha2": "b03ca870560b98ad347ac2594813a35ef0553dce" +} +,{ + "testCaseDescription": "javascript-for-loop-with-in-statement-delete-replacement-test", + "expectedResult": { + "changes": { + "for-loop-with-in-statement.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "for-loop-with-in-statement.js", + "end": [ + 1, + 73 + ] + } + }, + "summary": "Deleted the 'otherKey in something && i = 0; i < n; i++' for statement", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 1 + ], + "name": "for-loop-with-in-statement.js", + "end": [ + 2, + 63 + ] + } + }, + "summary": "Deleted the 'key in something && i = 0; i < n; i++' for statement", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "for-loop-with-in-statement.js", + "end": [ + 2, + 73 + ] + } + }, + "summary": "Added the 'otherKey in something && i = 0; i < n; i++' for statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "for-loop-with-in-statement.js" + ], + "sha1": "b03ca870560b98ad347ac2594813a35ef0553dce", + "gitDir": "test/corpus/repos/javascript", + "sha2": "6d1feba84dcea819e587e5b89f199ada2fb80c4a" +} +,{ + "testCaseDescription": "javascript-for-loop-with-in-statement-delete-test", + "expectedResult": { + "changes": { + "for-loop-with-in-statement.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "for-loop-with-in-statement.js", + "end": [ + 1, + 63 + ] + } + }, + "summary": "Deleted the 'key in something && i = 0; i < n; i++' for statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "for-loop-with-in-statement.js" + ], + "sha1": "6d1feba84dcea819e587e5b89f199ada2fb80c4a", + "gitDir": "test/corpus/repos/javascript", + "sha2": "dbe96e06dcfc57ed5f62e1ea8c3f7047030cbc10" +} +,{ + "testCaseDescription": "javascript-for-loop-with-in-statement-delete-rest-test", + "expectedResult": { + "changes": { + "for-loop-with-in-statement.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "for-loop-with-in-statement.js", + "end": [ + 1, + 73 + ] + } + }, + "summary": "Deleted the 'otherKey in something && i = 0; i < n; i++' for statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "for-loop-with-in-statement.js" + ], + "sha1": "dbe96e06dcfc57ed5f62e1ea8c3f7047030cbc10", + "gitDir": "test/corpus/repos/javascript", + "sha2": "2469dee56808315df426b5a3b5c3f45a32a5dead" +}] diff --git a/test/corpus/diff-summaries/javascript/for-of-statement.json b/test/corpus/diff-summaries/javascript/for-of-statement.json new file mode 100644 index 000000000..9b9648080 --- /dev/null +++ b/test/corpus/diff-summaries/javascript/for-of-statement.json @@ -0,0 +1,428 @@ +[{ + "testCaseDescription": "javascript-for-of-statement-insert-test", + "expectedResult": { + "changes": { + "for-of-statement.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "for-of-statement.js", + "end": [ + 1, + 43 + ] + } + }, + "summary": "Added the 'item of items' for statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "for-of-statement.js" + ], + "sha1": "2469dee56808315df426b5a3b5c3f45a32a5dead", + "gitDir": "test/corpus/repos/javascript", + "sha2": "cbe403e75ef47b35c182df6b7afe73ad796fab8a" +} +,{ + "testCaseDescription": "javascript-for-of-statement-replacement-insert-test", + "expectedResult": { + "changes": { + "for-of-statement.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "for-of-statement.js", + "end": [ + 1, + 46 + ] + } + }, + "summary": "Added the 'thing of things' for statement", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "for-of-statement.js", + "end": [ + 2, + 43 + ] + } + }, + "summary": "Added the 'item of items' for statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "for-of-statement.js" + ], + "sha1": "cbe403e75ef47b35c182df6b7afe73ad796fab8a", + "gitDir": "test/corpus/repos/javascript", + "sha2": "155a0705e326c3ff582ee652fed52550677570a6" +} +,{ + "testCaseDescription": "javascript-for-of-statement-delete-insert-test", + "expectedResult": { + "changes": { + "for-of-statement.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 10 + ], + "name": "for-of-statement.js", + "end": [ + 1, + 15 + ] + }, + { + "start": [ + 1, + 10 + ], + "name": "for-of-statement.js", + "end": [ + 1, + 14 + ] + } + ] + }, + "summary": "Replaced the 'thing' identifier with the 'item' identifier", + "tag": "JSONSummary" + }, + { + "span": { + "these": [ + { + "start": [ + 1, + 19 + ], + "name": "for-of-statement.js", + "end": [ + 1, + 25 + ] + }, + { + "start": [ + 1, + 18 + ], + "name": "for-of-statement.js", + "end": [ + 1, + 23 + ] + } + ] + }, + "summary": "Replaced the 'things' identifier with the 'items' identifier", + "tag": "JSONSummary" + }, + { + "span": { + "these": [ + { + "start": [ + 1, + 37 + ], + "name": "for-of-statement.js", + "end": [ + 1, + 42 + ] + }, + { + "start": [ + 1, + 35 + ], + "name": "for-of-statement.js", + "end": [ + 1, + 39 + ] + } + ] + }, + "summary": "Replaced the 'thing' identifier with the 'item' identifier in the process(item) function call", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "for-of-statement.js" + ], + "sha1": "155a0705e326c3ff582ee652fed52550677570a6", + "gitDir": "test/corpus/repos/javascript", + "sha2": "ef8d8643334cebf32c2c4be0f8efab6bc8efbc2b" +} +,{ + "testCaseDescription": "javascript-for-of-statement-replacement-test", + "expectedResult": { + "changes": { + "for-of-statement.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 10 + ], + "name": "for-of-statement.js", + "end": [ + 1, + 14 + ] + }, + { + "start": [ + 1, + 10 + ], + "name": "for-of-statement.js", + "end": [ + 1, + 15 + ] + } + ] + }, + "summary": "Replaced the 'item' identifier with the 'thing' identifier", + "tag": "JSONSummary" + }, + { + "span": { + "these": [ + { + "start": [ + 1, + 18 + ], + "name": "for-of-statement.js", + "end": [ + 1, + 23 + ] + }, + { + "start": [ + 1, + 19 + ], + "name": "for-of-statement.js", + "end": [ + 1, + 25 + ] + } + ] + }, + "summary": "Replaced the 'items' identifier with the 'things' identifier", + "tag": "JSONSummary" + }, + { + "span": { + "these": [ + { + "start": [ + 1, + 35 + ], + "name": "for-of-statement.js", + "end": [ + 1, + 39 + ] + }, + { + "start": [ + 1, + 37 + ], + "name": "for-of-statement.js", + "end": [ + 1, + 42 + ] + } + ] + }, + "summary": "Replaced the 'item' identifier with the 'thing' identifier in the process(thing) function call", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "for-of-statement.js" + ], + "sha1": "ef8d8643334cebf32c2c4be0f8efab6bc8efbc2b", + "gitDir": "test/corpus/repos/javascript", + "sha2": "fca6551e597967f1b7970eba8647ea449d642c0d" +} +,{ + "testCaseDescription": "javascript-for-of-statement-delete-replacement-test", + "expectedResult": { + "changes": { + "for-of-statement.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "for-of-statement.js", + "end": [ + 1, + 46 + ] + } + }, + "summary": "Deleted the 'thing of things' for statement", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 1 + ], + "name": "for-of-statement.js", + "end": [ + 2, + 43 + ] + } + }, + "summary": "Deleted the 'item of items' for statement", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "for-of-statement.js", + "end": [ + 2, + 46 + ] + } + }, + "summary": "Added the 'thing of things' for statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "for-of-statement.js" + ], + "sha1": "fca6551e597967f1b7970eba8647ea449d642c0d", + "gitDir": "test/corpus/repos/javascript", + "sha2": "951e6473bd1c1c48a8ccf17b85edf71c30f68003" +} +,{ + "testCaseDescription": "javascript-for-of-statement-delete-test", + "expectedResult": { + "changes": { + "for-of-statement.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "for-of-statement.js", + "end": [ + 1, + 43 + ] + } + }, + "summary": "Deleted the 'item of items' for statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "for-of-statement.js" + ], + "sha1": "951e6473bd1c1c48a8ccf17b85edf71c30f68003", + "gitDir": "test/corpus/repos/javascript", + "sha2": "eb9af080f71a3ebd4faf827ba73ca5506a0078bb" +} +,{ + "testCaseDescription": "javascript-for-of-statement-delete-rest-test", + "expectedResult": { + "changes": { + "for-of-statement.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "for-of-statement.js", + "end": [ + 1, + 46 + ] + } + }, + "summary": "Deleted the 'thing of things' for statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "for-of-statement.js" + ], + "sha1": "eb9af080f71a3ebd4faf827ba73ca5506a0078bb", + "gitDir": "test/corpus/repos/javascript", + "sha2": "4baec39517b6fe2e913b63502b66c0f5bb4ad2cc" +}] diff --git a/test/corpus/diff-summaries/javascript/for-statement.json b/test/corpus/diff-summaries/javascript/for-statement.json new file mode 100644 index 000000000..e407c3150 --- /dev/null +++ b/test/corpus/diff-summaries/javascript/for-statement.json @@ -0,0 +1,308 @@ +[{ + "testCaseDescription": "javascript-for-statement-insert-test", + "expectedResult": { + "changes": { + "for-statement.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "for-statement.js", + "end": [ + 1, + 45 + ] + } + }, + "summary": "Added the 'i = 0, init(); i < 10; i++' for statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "for-statement.js" + ], + "sha1": "8c6579c037e31738b4decb4405d7a17824524ca3", + "gitDir": "test/corpus/repos/javascript", + "sha2": "8acb9b3de3ca8787d948acb4a99f00d03cee5b3e" +} +,{ + "testCaseDescription": "javascript-for-statement-replacement-insert-test", + "expectedResult": { + "changes": { + "for-statement.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "for-statement.js", + "end": [ + 1, + 46 + ] + } + }, + "summary": "Added the 'i = 0, init(); i < 100; i++' for statement", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "for-statement.js", + "end": [ + 2, + 45 + ] + } + }, + "summary": "Added the 'i = 0, init(); i < 10; i++' for statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "for-statement.js" + ], + "sha1": "8acb9b3de3ca8787d948acb4a99f00d03cee5b3e", + "gitDir": "test/corpus/repos/javascript", + "sha2": "8e51e424b4a6aca62377fa98a82aeaa8e9ddce55" +} +,{ + "testCaseDescription": "javascript-for-statement-delete-insert-test", + "expectedResult": { + "changes": { + "for-statement.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 25 + ], + "name": "for-statement.js", + "end": [ + 1, + 28 + ] + }, + { + "start": [ + 1, + 25 + ], + "name": "for-statement.js", + "end": [ + 1, + 27 + ] + } + ] + }, + "summary": "Replaced '100' with '10'", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "for-statement.js" + ], + "sha1": "8e51e424b4a6aca62377fa98a82aeaa8e9ddce55", + "gitDir": "test/corpus/repos/javascript", + "sha2": "c0acf9cf01a97524f0c44297d9f448881a381f67" +} +,{ + "testCaseDescription": "javascript-for-statement-replacement-test", + "expectedResult": { + "changes": { + "for-statement.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 25 + ], + "name": "for-statement.js", + "end": [ + 1, + 27 + ] + }, + { + "start": [ + 1, + 25 + ], + "name": "for-statement.js", + "end": [ + 1, + 28 + ] + } + ] + }, + "summary": "Replaced '10' with '100'", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "for-statement.js" + ], + "sha1": "c0acf9cf01a97524f0c44297d9f448881a381f67", + "gitDir": "test/corpus/repos/javascript", + "sha2": "5253024f0a55122448f8b16a6869686fcb3b9fa1" +} +,{ + "testCaseDescription": "javascript-for-statement-delete-replacement-test", + "expectedResult": { + "changes": { + "for-statement.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "for-statement.js", + "end": [ + 1, + 46 + ] + } + }, + "summary": "Deleted the 'i = 0, init(); i < 100; i++' for statement", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 1 + ], + "name": "for-statement.js", + "end": [ + 2, + 45 + ] + } + }, + "summary": "Deleted the 'i = 0, init(); i < 10; i++' for statement", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "for-statement.js", + "end": [ + 2, + 46 + ] + } + }, + "summary": "Added the 'i = 0, init(); i < 100; i++' for statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "for-statement.js" + ], + "sha1": "5253024f0a55122448f8b16a6869686fcb3b9fa1", + "gitDir": "test/corpus/repos/javascript", + "sha2": "3a720565a0493ccf4374590f8b8314b29d642fa0" +} +,{ + "testCaseDescription": "javascript-for-statement-delete-test", + "expectedResult": { + "changes": { + "for-statement.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "for-statement.js", + "end": [ + 1, + 45 + ] + } + }, + "summary": "Deleted the 'i = 0, init(); i < 10; i++' for statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "for-statement.js" + ], + "sha1": "3a720565a0493ccf4374590f8b8314b29d642fa0", + "gitDir": "test/corpus/repos/javascript", + "sha2": "2fbfe01a9a42d1f7bc719d35bc67e51164dfac6c" +} +,{ + "testCaseDescription": "javascript-for-statement-delete-rest-test", + "expectedResult": { + "changes": { + "for-statement.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "for-statement.js", + "end": [ + 1, + 46 + ] + } + }, + "summary": "Deleted the 'i = 0, init(); i < 100; i++' for statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "for-statement.js" + ], + "sha1": "2fbfe01a9a42d1f7bc719d35bc67e51164dfac6c", + "gitDir": "test/corpus/repos/javascript", + "sha2": "1689419def381340a06222171173117f80ab169e" +}] diff --git a/test/corpus/diff-summaries/javascript/function-call-args.json b/test/corpus/diff-summaries/javascript/function-call-args.json new file mode 100644 index 000000000..8dd954247 --- /dev/null +++ b/test/corpus/diff-summaries/javascript/function-call-args.json @@ -0,0 +1,608 @@ +[{ + "testCaseDescription": "javascript-function-call-args-insert-test", + "expectedResult": { + "changes": { + "function-call-args.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "function-call-args.js", + "end": [ + 1, + 77 + ] + } + }, + "summary": "Added the 'someFunction(1, \"string\", …, true)' function call", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "function-call-args.js" + ], + "sha1": "7a9cdc6c356ec1e7fe6e47c923898d3e2e6a32cc", + "gitDir": "test/corpus/repos/javascript", + "sha2": "183f0fed6e757160eafedb9d7740cdfdb28bec21" +} +,{ + "testCaseDescription": "javascript-function-call-args-replacement-insert-test", + "expectedResult": { + "changes": { + "function-call-args.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "function-call-args.js", + "end": [ + 1, + 83 + ] + } + }, + "summary": "Added the 'someFunction(1, \"otherString\", …, false)' function call", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "function-call-args.js", + "end": [ + 2, + 77 + ] + } + }, + "summary": "Added the 'someFunction(1, \"string\", …, true)' function call", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "function-call-args.js" + ], + "sha1": "183f0fed6e757160eafedb9d7740cdfdb28bec21", + "gitDir": "test/corpus/repos/javascript", + "sha2": "b30012eb0ae7cdbcb6a55ce2ada5ead28b4d09d5" +} +,{ + "testCaseDescription": "javascript-function-call-args-delete-insert-test", + "expectedResult": { + "changes": { + "function-call-args.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 17 + ], + "name": "function-call-args.js", + "end": [ + 1, + 30 + ] + }, + { + "start": [ + 1, + 17 + ], + "name": "function-call-args.js", + "end": [ + 1, + 25 + ] + } + ] + }, + "summary": "Replaced the \"otherString\" string with the \"string\" string in the someFunction(1, \"string\", …, true) function call", + "tag": "JSONSummary" + }, + { + "span": { + "these": [ + { + "start": [ + 1, + 41 + ], + "name": "function-call-args.js", + "end": [ + 1, + 42 + ] + }, + { + "start": [ + 1, + 36 + ], + "name": "function-call-args.js", + "end": [ + 1, + 37 + ] + } + ] + }, + "summary": "Replaced the 'b' identifier with the 'a' identifier in the someFunction(1, \"string\", …, true) function call", + "tag": "JSONSummary" + }, + { + "span": { + "these": [ + { + "start": [ + 1, + 43 + ], + "name": "function-call-args.js", + "end": [ + 1, + 44 + ] + }, + { + "start": [ + 1, + 38 + ], + "name": "function-call-args.js", + "end": [ + 1, + 39 + ] + } + ] + }, + "summary": "Replaced the 'c' identifier with the 'b' identifier in the someFunction(1, \"string\", …, true) function call", + "tag": "JSONSummary" + }, + { + "span": { + "these": [ + { + "start": [ + 1, + 60 + ], + "name": "function-call-args.js", + "end": [ + 1, + 61 + ] + }, + { + "start": [ + 1, + 55 + ], + "name": "function-call-args.js", + "end": [ + 1, + 56 + ] + } + ] + }, + "summary": "Replaced the 'b' identifier with the 'a' identifier in the console.log(a) method call", + "tag": "JSONSummary" + }, + { + "span": { + "these": [ + { + "start": [ + 1, + 71 + ], + "name": "function-call-args.js", + "end": [ + 1, + 72 + ] + }, + { + "start": [ + 1, + 66 + ], + "name": "function-call-args.js", + "end": [ + 1, + 67 + ] + } + ] + }, + "summary": "Replaced the 'c' identifier with the 'b' identifier in the someFunction(1, \"string\", …, true) function call", + "tag": "JSONSummary" + }, + { + "span": { + "these": [ + { + "start": [ + 1, + 77 + ], + "name": "function-call-args.js", + "end": [ + 1, + 82 + ] + }, + { + "start": [ + 1, + 72 + ], + "name": "function-call-args.js", + "end": [ + 1, + 76 + ] + } + ] + }, + "summary": "Replaced 'false' with 'true' in the someFunction(1, \"string\", …, true) function call", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "function-call-args.js" + ], + "sha1": "b30012eb0ae7cdbcb6a55ce2ada5ead28b4d09d5", + "gitDir": "test/corpus/repos/javascript", + "sha2": "1f00971ae667503452bec939433970cf2f5a1ef9" +} +,{ + "testCaseDescription": "javascript-function-call-args-replacement-test", + "expectedResult": { + "changes": { + "function-call-args.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 17 + ], + "name": "function-call-args.js", + "end": [ + 1, + 25 + ] + }, + { + "start": [ + 1, + 17 + ], + "name": "function-call-args.js", + "end": [ + 1, + 30 + ] + } + ] + }, + "summary": "Replaced the \"string\" string with the \"otherString\" string in the someFunction(1, \"otherString\", …, false) function call", + "tag": "JSONSummary" + }, + { + "span": { + "these": [ + { + "start": [ + 1, + 36 + ], + "name": "function-call-args.js", + "end": [ + 1, + 37 + ] + }, + { + "start": [ + 1, + 41 + ], + "name": "function-call-args.js", + "end": [ + 1, + 42 + ] + } + ] + }, + "summary": "Replaced the 'a' identifier with the 'b' identifier in the someFunction(1, \"otherString\", …, false) function call", + "tag": "JSONSummary" + }, + { + "span": { + "these": [ + { + "start": [ + 1, + 38 + ], + "name": "function-call-args.js", + "end": [ + 1, + 39 + ] + }, + { + "start": [ + 1, + 43 + ], + "name": "function-call-args.js", + "end": [ + 1, + 44 + ] + } + ] + }, + "summary": "Replaced the 'b' identifier with the 'c' identifier in the someFunction(1, \"otherString\", …, false) function call", + "tag": "JSONSummary" + }, + { + "span": { + "these": [ + { + "start": [ + 1, + 55 + ], + "name": "function-call-args.js", + "end": [ + 1, + 56 + ] + }, + { + "start": [ + 1, + 60 + ], + "name": "function-call-args.js", + "end": [ + 1, + 61 + ] + } + ] + }, + "summary": "Replaced the 'a' identifier with the 'b' identifier in the console.log(b) method call", + "tag": "JSONSummary" + }, + { + "span": { + "these": [ + { + "start": [ + 1, + 66 + ], + "name": "function-call-args.js", + "end": [ + 1, + 67 + ] + }, + { + "start": [ + 1, + 71 + ], + "name": "function-call-args.js", + "end": [ + 1, + 72 + ] + } + ] + }, + "summary": "Replaced the 'b' identifier with the 'c' identifier in the someFunction(1, \"otherString\", …, false) function call", + "tag": "JSONSummary" + }, + { + "span": { + "these": [ + { + "start": [ + 1, + 72 + ], + "name": "function-call-args.js", + "end": [ + 1, + 76 + ] + }, + { + "start": [ + 1, + 77 + ], + "name": "function-call-args.js", + "end": [ + 1, + 82 + ] + } + ] + }, + "summary": "Replaced 'true' with 'false' in the someFunction(1, \"otherString\", …, false) function call", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "function-call-args.js" + ], + "sha1": "1f00971ae667503452bec939433970cf2f5a1ef9", + "gitDir": "test/corpus/repos/javascript", + "sha2": "7f80f26bf5f8baacf47c9d7ad830572b46738b56" +} +,{ + "testCaseDescription": "javascript-function-call-args-delete-replacement-test", + "expectedResult": { + "changes": { + "function-call-args.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "function-call-args.js", + "end": [ + 1, + 83 + ] + } + }, + "summary": "Deleted the 'someFunction(1, \"otherString\", …, false)' function call", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 1 + ], + "name": "function-call-args.js", + "end": [ + 2, + 77 + ] + } + }, + "summary": "Deleted the 'someFunction(1, \"string\", …, true)' function call", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "function-call-args.js", + "end": [ + 2, + 83 + ] + } + }, + "summary": "Added the 'someFunction(1, \"otherString\", …, false)' function call", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "function-call-args.js" + ], + "sha1": "7f80f26bf5f8baacf47c9d7ad830572b46738b56", + "gitDir": "test/corpus/repos/javascript", + "sha2": "3e16e4bb994195b7c5a841f3e585c332c7aaf578" +} +,{ + "testCaseDescription": "javascript-function-call-args-delete-test", + "expectedResult": { + "changes": { + "function-call-args.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "function-call-args.js", + "end": [ + 1, + 77 + ] + } + }, + "summary": "Deleted the 'someFunction(1, \"string\", …, true)' function call", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "function-call-args.js" + ], + "sha1": "3e16e4bb994195b7c5a841f3e585c332c7aaf578", + "gitDir": "test/corpus/repos/javascript", + "sha2": "091f7c6596e348e44e3679375e57eddc657a73a3" +} +,{ + "testCaseDescription": "javascript-function-call-args-delete-rest-test", + "expectedResult": { + "changes": { + "function-call-args.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "function-call-args.js", + "end": [ + 1, + 83 + ] + } + }, + "summary": "Deleted the 'someFunction(1, \"otherString\", …, false)' function call", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "function-call-args.js" + ], + "sha1": "091f7c6596e348e44e3679375e57eddc657a73a3", + "gitDir": "test/corpus/repos/javascript", + "sha2": "e67227e82c01378ae1102d7579e52a47e06ef16a" +}] diff --git a/test/corpus/diff-summaries/javascript/function-call.json b/test/corpus/diff-summaries/javascript/function-call.json new file mode 100644 index 000000000..a4341f8be --- /dev/null +++ b/test/corpus/diff-summaries/javascript/function-call.json @@ -0,0 +1,308 @@ +[{ + "testCaseDescription": "javascript-function-call-insert-test", + "expectedResult": { + "changes": { + "function-call.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "function-call.js", + "end": [ + 1, + 27 + ] + } + }, + "summary": "Added the 'someFunction(arg1, \"arg2\")' function call", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "function-call.js" + ], + "sha1": "66f76d6c6d3a517f3f4c016d8e03d3497cf724c6", + "gitDir": "test/corpus/repos/javascript", + "sha2": "04ae6b563749c2b0fcca12174eb5398356c67a8e" +} +,{ + "testCaseDescription": "javascript-function-call-replacement-insert-test", + "expectedResult": { + "changes": { + "function-call.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "function-call.js", + "end": [ + 1, + 27 + ] + } + }, + "summary": "Added the 'someFunction(arg1, \"arg3\")' function call", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "function-call.js", + "end": [ + 2, + 27 + ] + } + }, + "summary": "Added the 'someFunction(arg1, \"arg2\")' function call", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "function-call.js" + ], + "sha1": "04ae6b563749c2b0fcca12174eb5398356c67a8e", + "gitDir": "test/corpus/repos/javascript", + "sha2": "f6af23e39ba5fd5b1d1733db2141a70d65534f41" +} +,{ + "testCaseDescription": "javascript-function-call-delete-insert-test", + "expectedResult": { + "changes": { + "function-call.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 20 + ], + "name": "function-call.js", + "end": [ + 1, + 26 + ] + }, + { + "start": [ + 1, + 20 + ], + "name": "function-call.js", + "end": [ + 1, + 26 + ] + } + ] + }, + "summary": "Replaced the \"arg3\" string with the \"arg2\" string in the someFunction(arg1, \"arg2\") function call", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "function-call.js" + ], + "sha1": "f6af23e39ba5fd5b1d1733db2141a70d65534f41", + "gitDir": "test/corpus/repos/javascript", + "sha2": "f6c31c3c422ab05b2d0bba725022eeabcaa3739f" +} +,{ + "testCaseDescription": "javascript-function-call-replacement-test", + "expectedResult": { + "changes": { + "function-call.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 20 + ], + "name": "function-call.js", + "end": [ + 1, + 26 + ] + }, + { + "start": [ + 1, + 20 + ], + "name": "function-call.js", + "end": [ + 1, + 26 + ] + } + ] + }, + "summary": "Replaced the \"arg2\" string with the \"arg3\" string in the someFunction(arg1, \"arg3\") function call", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "function-call.js" + ], + "sha1": "f6c31c3c422ab05b2d0bba725022eeabcaa3739f", + "gitDir": "test/corpus/repos/javascript", + "sha2": "14e9613f11bf3b30e519ca68df0c2f4a9f153c40" +} +,{ + "testCaseDescription": "javascript-function-call-delete-replacement-test", + "expectedResult": { + "changes": { + "function-call.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "function-call.js", + "end": [ + 1, + 27 + ] + } + }, + "summary": "Deleted the 'someFunction(arg1, \"arg3\")' function call", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 1 + ], + "name": "function-call.js", + "end": [ + 2, + 27 + ] + } + }, + "summary": "Deleted the 'someFunction(arg1, \"arg2\")' function call", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "function-call.js", + "end": [ + 2, + 27 + ] + } + }, + "summary": "Added the 'someFunction(arg1, \"arg3\")' function call", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "function-call.js" + ], + "sha1": "14e9613f11bf3b30e519ca68df0c2f4a9f153c40", + "gitDir": "test/corpus/repos/javascript", + "sha2": "b8c0d83eeb28bd56aacfca81580c8e3217da7345" +} +,{ + "testCaseDescription": "javascript-function-call-delete-test", + "expectedResult": { + "changes": { + "function-call.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "function-call.js", + "end": [ + 1, + 27 + ] + } + }, + "summary": "Deleted the 'someFunction(arg1, \"arg2\")' function call", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "function-call.js" + ], + "sha1": "b8c0d83eeb28bd56aacfca81580c8e3217da7345", + "gitDir": "test/corpus/repos/javascript", + "sha2": "27dba7ea895c481db1cd34b80cf0ef484c718882" +} +,{ + "testCaseDescription": "javascript-function-call-delete-rest-test", + "expectedResult": { + "changes": { + "function-call.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "function-call.js", + "end": [ + 1, + 27 + ] + } + }, + "summary": "Deleted the 'someFunction(arg1, \"arg3\")' function call", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "function-call.js" + ], + "sha1": "27dba7ea895c481db1cd34b80cf0ef484c718882", + "gitDir": "test/corpus/repos/javascript", + "sha2": "bde44008cfb326f395ddb1071a073fc1113ffb3d" +}] diff --git a/test/corpus/diff-summaries/javascript/function.json b/test/corpus/diff-summaries/javascript/function.json new file mode 100644 index 000000000..cd35b2444 --- /dev/null +++ b/test/corpus/diff-summaries/javascript/function.json @@ -0,0 +1,308 @@ +[{ + "testCaseDescription": "javascript-function-insert-test", + "expectedResult": { + "changes": { + "function.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "function.js", + "end": [ + 1, + 31 + ] + } + }, + "summary": "Added an anonymous(arg1, arg2) function", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "function.js" + ], + "sha1": "7421caaeb3a46acf3fd36871e3fd56e4409df4c1", + "gitDir": "test/corpus/repos/javascript", + "sha2": "9eb28dc8e67375a2846a0a2baa6f91de7a54e3fc" +} +,{ + "testCaseDescription": "javascript-function-replacement-insert-test", + "expectedResult": { + "changes": { + "function.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "function.js", + "end": [ + 1, + 31 + ] + } + }, + "summary": "Added an anonymous(arg1, arg2) function", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "function.js", + "end": [ + 2, + 31 + ] + } + }, + "summary": "Added an anonymous(arg1, arg2) function", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "function.js" + ], + "sha1": "9eb28dc8e67375a2846a0a2baa6f91de7a54e3fc", + "gitDir": "test/corpus/repos/javascript", + "sha2": "f80644c146243f36bc8d53bd88b463f88fb56148" +} +,{ + "testCaseDescription": "javascript-function-delete-insert-test", + "expectedResult": { + "changes": { + "function.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 24 + ], + "name": "function.js", + "end": [ + 1, + 28 + ] + }, + { + "start": [ + 1, + 24 + ], + "name": "function.js", + "end": [ + 1, + 28 + ] + } + ] + }, + "summary": "Replaced the 'arg1' identifier with the 'arg2' identifier", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "function.js" + ], + "sha1": "f80644c146243f36bc8d53bd88b463f88fb56148", + "gitDir": "test/corpus/repos/javascript", + "sha2": "16e3dd70bc83125385a9b3f952e77b24b15558cd" +} +,{ + "testCaseDescription": "javascript-function-replacement-test", + "expectedResult": { + "changes": { + "function.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 24 + ], + "name": "function.js", + "end": [ + 1, + 28 + ] + }, + { + "start": [ + 1, + 24 + ], + "name": "function.js", + "end": [ + 1, + 28 + ] + } + ] + }, + "summary": "Replaced the 'arg2' identifier with the 'arg1' identifier", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "function.js" + ], + "sha1": "16e3dd70bc83125385a9b3f952e77b24b15558cd", + "gitDir": "test/corpus/repos/javascript", + "sha2": "610b235fd79ed384ca2ed512957629b75fdaec56" +} +,{ + "testCaseDescription": "javascript-function-delete-replacement-test", + "expectedResult": { + "changes": { + "function.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "function.js", + "end": [ + 1, + 31 + ] + } + }, + "summary": "Deleted an anonymous(arg1, arg2) function", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 1 + ], + "name": "function.js", + "end": [ + 2, + 31 + ] + } + }, + "summary": "Deleted an anonymous(arg1, arg2) function", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "function.js", + "end": [ + 2, + 31 + ] + } + }, + "summary": "Added an anonymous(arg1, arg2) function", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "function.js" + ], + "sha1": "610b235fd79ed384ca2ed512957629b75fdaec56", + "gitDir": "test/corpus/repos/javascript", + "sha2": "c11cac612eb21c4dd32f29b5fdcbb77431bc1478" +} +,{ + "testCaseDescription": "javascript-function-delete-test", + "expectedResult": { + "changes": { + "function.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "function.js", + "end": [ + 1, + 31 + ] + } + }, + "summary": "Deleted an anonymous(arg1, arg2) function", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "function.js" + ], + "sha1": "c11cac612eb21c4dd32f29b5fdcbb77431bc1478", + "gitDir": "test/corpus/repos/javascript", + "sha2": "dfa9a3bf7f53d0621d490ae446682bcf37e6c2b9" +} +,{ + "testCaseDescription": "javascript-function-delete-rest-test", + "expectedResult": { + "changes": { + "function.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "function.js", + "end": [ + 1, + 31 + ] + } + }, + "summary": "Deleted an anonymous(arg1, arg2) function", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "function.js" + ], + "sha1": "dfa9a3bf7f53d0621d490ae446682bcf37e6c2b9", + "gitDir": "test/corpus/repos/javascript", + "sha2": "1331d4ffb544aebfa16c17c9c2ebbab19e6f422a" +}] diff --git a/test/corpus/diff-summaries/javascript/generator-function.json b/test/corpus/diff-summaries/javascript/generator-function.json new file mode 100644 index 000000000..89d303361 --- /dev/null +++ b/test/corpus/diff-summaries/javascript/generator-function.json @@ -0,0 +1,308 @@ +[{ + "testCaseDescription": "javascript-generator-function-insert-test", + "expectedResult": { + "changes": { + "generator-function.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "generator-function.js", + "end": [ + 1, + 59 + ] + } + }, + "summary": "Added the 'generateStuff' function", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "generator-function.js" + ], + "sha1": "4d63196a05b9443aebe166c10eaf31d60a162f7e", + "gitDir": "test/corpus/repos/javascript", + "sha2": "36b15111da4c3d7db3722d53889c04ec06472bf7" +} +,{ + "testCaseDescription": "javascript-generator-function-replacement-insert-test", + "expectedResult": { + "changes": { + "generator-function.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "generator-function.js", + "end": [ + 1, + 62 + ] + } + }, + "summary": "Added the 'generateNewStuff' function", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "generator-function.js", + "end": [ + 2, + 59 + ] + } + }, + "summary": "Added the 'generateStuff' function", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "generator-function.js" + ], + "sha1": "36b15111da4c3d7db3722d53889c04ec06472bf7", + "gitDir": "test/corpus/repos/javascript", + "sha2": "4c88f30a1529bc19cf1c5f0e96db7046c3020301" +} +,{ + "testCaseDescription": "javascript-generator-function-delete-insert-test", + "expectedResult": { + "changes": { + "generator-function.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 11 + ], + "name": "generator-function.js", + "end": [ + 1, + 27 + ] + }, + { + "start": [ + 1, + 11 + ], + "name": "generator-function.js", + "end": [ + 1, + 24 + ] + } + ] + }, + "summary": "Replaced the 'generateNewStuff' identifier with the 'generateStuff' identifier in the generateStuff function", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "generator-function.js" + ], + "sha1": "4c88f30a1529bc19cf1c5f0e96db7046c3020301", + "gitDir": "test/corpus/repos/javascript", + "sha2": "a688e4e430dca4e71ee900724635db302ea27a0a" +} +,{ + "testCaseDescription": "javascript-generator-function-replacement-test", + "expectedResult": { + "changes": { + "generator-function.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 11 + ], + "name": "generator-function.js", + "end": [ + 1, + 24 + ] + }, + { + "start": [ + 1, + 11 + ], + "name": "generator-function.js", + "end": [ + 1, + 27 + ] + } + ] + }, + "summary": "Replaced the 'generateStuff' identifier with the 'generateNewStuff' identifier in the generateNewStuff function", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "generator-function.js" + ], + "sha1": "a688e4e430dca4e71ee900724635db302ea27a0a", + "gitDir": "test/corpus/repos/javascript", + "sha2": "39e1e3960d0368f451e694779a82ef34e1a9270b" +} +,{ + "testCaseDescription": "javascript-generator-function-delete-replacement-test", + "expectedResult": { + "changes": { + "generator-function.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "generator-function.js", + "end": [ + 1, + 62 + ] + } + }, + "summary": "Deleted the 'generateNewStuff' function", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 1 + ], + "name": "generator-function.js", + "end": [ + 2, + 59 + ] + } + }, + "summary": "Deleted the 'generateStuff' function", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "generator-function.js", + "end": [ + 2, + 62 + ] + } + }, + "summary": "Added the 'generateNewStuff' function", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "generator-function.js" + ], + "sha1": "39e1e3960d0368f451e694779a82ef34e1a9270b", + "gitDir": "test/corpus/repos/javascript", + "sha2": "782a8e72f3f39f9557c1b5653ddec71dcdd5fb56" +} +,{ + "testCaseDescription": "javascript-generator-function-delete-test", + "expectedResult": { + "changes": { + "generator-function.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "generator-function.js", + "end": [ + 1, + 59 + ] + } + }, + "summary": "Deleted the 'generateStuff' function", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "generator-function.js" + ], + "sha1": "782a8e72f3f39f9557c1b5653ddec71dcdd5fb56", + "gitDir": "test/corpus/repos/javascript", + "sha2": "f88a7087ddff6c06546b3e0124f7ca8d94d409f8" +} +,{ + "testCaseDescription": "javascript-generator-function-delete-rest-test", + "expectedResult": { + "changes": { + "generator-function.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "generator-function.js", + "end": [ + 1, + 62 + ] + } + }, + "summary": "Deleted the 'generateNewStuff' function", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "generator-function.js" + ], + "sha1": "f88a7087ddff6c06546b3e0124f7ca8d94d409f8", + "gitDir": "test/corpus/repos/javascript", + "sha2": "5fe4477fe4c9d164946d8aaf8fe66f107b0901b4" +}] diff --git a/test/corpus/diff-summaries/javascript/identifier.json b/test/corpus/diff-summaries/javascript/identifier.json new file mode 100644 index 000000000..0cc55db05 --- /dev/null +++ b/test/corpus/diff-summaries/javascript/identifier.json @@ -0,0 +1,308 @@ +[{ + "testCaseDescription": "javascript-identifier-insert-test", + "expectedResult": { + "changes": { + "identifier.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "identifier.js", + "end": [ + 1, + 7 + ] + } + }, + "summary": "Added the 'theVar' identifier", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "identifier.js" + ], + "sha1": "8bed39ae9a7d7acce7400df7173470825fa46cb0", + "gitDir": "test/corpus/repos/javascript", + "sha2": "adad30bc5133d1c447dc340517b42feaf646ba53" +} +,{ + "testCaseDescription": "javascript-identifier-replacement-insert-test", + "expectedResult": { + "changes": { + "identifier.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "identifier.js", + "end": [ + 1, + 8 + ] + } + }, + "summary": "Added the 'theVar2' identifier", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "identifier.js", + "end": [ + 2, + 7 + ] + } + }, + "summary": "Added the 'theVar' identifier", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "identifier.js" + ], + "sha1": "adad30bc5133d1c447dc340517b42feaf646ba53", + "gitDir": "test/corpus/repos/javascript", + "sha2": "0c71a54b8d1ef900aed495431e66ca7e1aabda5c" +} +,{ + "testCaseDescription": "javascript-identifier-delete-insert-test", + "expectedResult": { + "changes": { + "identifier.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 1 + ], + "name": "identifier.js", + "end": [ + 1, + 8 + ] + }, + { + "start": [ + 1, + 1 + ], + "name": "identifier.js", + "end": [ + 1, + 7 + ] + } + ] + }, + "summary": "Replaced the 'theVar2' identifier with the 'theVar' identifier", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "identifier.js" + ], + "sha1": "0c71a54b8d1ef900aed495431e66ca7e1aabda5c", + "gitDir": "test/corpus/repos/javascript", + "sha2": "f5b7d7c4e2697f8512daa4cbc1b98b1a08cf12ec" +} +,{ + "testCaseDescription": "javascript-identifier-replacement-test", + "expectedResult": { + "changes": { + "identifier.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 1 + ], + "name": "identifier.js", + "end": [ + 1, + 7 + ] + }, + { + "start": [ + 1, + 1 + ], + "name": "identifier.js", + "end": [ + 1, + 8 + ] + } + ] + }, + "summary": "Replaced the 'theVar' identifier with the 'theVar2' identifier", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "identifier.js" + ], + "sha1": "f5b7d7c4e2697f8512daa4cbc1b98b1a08cf12ec", + "gitDir": "test/corpus/repos/javascript", + "sha2": "316ee9b49a7790b81670a4d92a78ab982df69c03" +} +,{ + "testCaseDescription": "javascript-identifier-delete-replacement-test", + "expectedResult": { + "changes": { + "identifier.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "identifier.js", + "end": [ + 1, + 8 + ] + } + }, + "summary": "Deleted the 'theVar2' identifier", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 1 + ], + "name": "identifier.js", + "end": [ + 2, + 7 + ] + } + }, + "summary": "Deleted the 'theVar' identifier", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "identifier.js", + "end": [ + 2, + 8 + ] + } + }, + "summary": "Added the 'theVar2' identifier", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "identifier.js" + ], + "sha1": "316ee9b49a7790b81670a4d92a78ab982df69c03", + "gitDir": "test/corpus/repos/javascript", + "sha2": "78d921b09f5d8adc2a6fa113a032252aca288d47" +} +,{ + "testCaseDescription": "javascript-identifier-delete-test", + "expectedResult": { + "changes": { + "identifier.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "identifier.js", + "end": [ + 1, + 7 + ] + } + }, + "summary": "Deleted the 'theVar' identifier", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "identifier.js" + ], + "sha1": "78d921b09f5d8adc2a6fa113a032252aca288d47", + "gitDir": "test/corpus/repos/javascript", + "sha2": "beb075d5569a09221ee45c35159e37ac9d9cec4c" +} +,{ + "testCaseDescription": "javascript-identifier-delete-rest-test", + "expectedResult": { + "changes": { + "identifier.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "identifier.js", + "end": [ + 1, + 8 + ] + } + }, + "summary": "Deleted the 'theVar2' identifier", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "identifier.js" + ], + "sha1": "beb075d5569a09221ee45c35159e37ac9d9cec4c", + "gitDir": "test/corpus/repos/javascript", + "sha2": "7a8a0da7d72fa0fc4f17e0877fbf7991771801e4" +}] diff --git a/test/corpus/diff-summaries/javascript/if-else.json b/test/corpus/diff-summaries/javascript/if-else.json new file mode 100644 index 000000000..2a4a66e17 --- /dev/null +++ b/test/corpus/diff-summaries/javascript/if-else.json @@ -0,0 +1,308 @@ +[{ + "testCaseDescription": "javascript-if-else-insert-test", + "expectedResult": { + "changes": { + "if-else.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "if-else.js", + "end": [ + 1, + 25 + ] + } + }, + "summary": "Added the 'x' if statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "if-else.js" + ], + "sha1": "a6070e9c94930a94f1913e69bef6da80923cbfde", + "gitDir": "test/corpus/repos/javascript", + "sha2": "e6b1c046a9f61b81b0646a0d24ce02db7f461209" +} +,{ + "testCaseDescription": "javascript-if-else-replacement-insert-test", + "expectedResult": { + "changes": { + "if-else.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "if-else.js", + "end": [ + 1, + 29 + ] + } + }, + "summary": "Added the 'a' if statement", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "if-else.js", + "end": [ + 2, + 25 + ] + } + }, + "summary": "Added the 'x' if statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "if-else.js" + ], + "sha1": "e6b1c046a9f61b81b0646a0d24ce02db7f461209", + "gitDir": "test/corpus/repos/javascript", + "sha2": "8c1d085746a786b9f1f97a1df047a777ba9958f6" +} +,{ + "testCaseDescription": "javascript-if-else-delete-insert-test", + "expectedResult": { + "changes": { + "if-else.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 1 + ], + "name": "if-else.js", + "end": [ + 1, + 29 + ] + }, + { + "start": [ + 1, + 1 + ], + "name": "if-else.js", + "end": [ + 1, + 25 + ] + } + ] + }, + "summary": "Replaced the 'a' if statement with the 'x' if statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "if-else.js" + ], + "sha1": "8c1d085746a786b9f1f97a1df047a777ba9958f6", + "gitDir": "test/corpus/repos/javascript", + "sha2": "a4a9d189ba9f43fb4e56f0c5c7d26b8f24bd8fb9" +} +,{ + "testCaseDescription": "javascript-if-else-replacement-test", + "expectedResult": { + "changes": { + "if-else.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 1 + ], + "name": "if-else.js", + "end": [ + 1, + 25 + ] + }, + { + "start": [ + 1, + 1 + ], + "name": "if-else.js", + "end": [ + 1, + 29 + ] + } + ] + }, + "summary": "Replaced the 'x' if statement with the 'a' if statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "if-else.js" + ], + "sha1": "a4a9d189ba9f43fb4e56f0c5c7d26b8f24bd8fb9", + "gitDir": "test/corpus/repos/javascript", + "sha2": "b279cca2a52da34fc8487e65af5f74d2e3d156ee" +} +,{ + "testCaseDescription": "javascript-if-else-delete-replacement-test", + "expectedResult": { + "changes": { + "if-else.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "if-else.js", + "end": [ + 1, + 29 + ] + } + }, + "summary": "Deleted the 'a' if statement", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 1 + ], + "name": "if-else.js", + "end": [ + 2, + 25 + ] + } + }, + "summary": "Deleted the 'x' if statement", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "if-else.js", + "end": [ + 2, + 29 + ] + } + }, + "summary": "Added the 'a' if statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "if-else.js" + ], + "sha1": "b279cca2a52da34fc8487e65af5f74d2e3d156ee", + "gitDir": "test/corpus/repos/javascript", + "sha2": "13a7419cb57d66ff977bcee43d8a447cb77977ed" +} +,{ + "testCaseDescription": "javascript-if-else-delete-test", + "expectedResult": { + "changes": { + "if-else.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "if-else.js", + "end": [ + 1, + 25 + ] + } + }, + "summary": "Deleted the 'x' if statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "if-else.js" + ], + "sha1": "13a7419cb57d66ff977bcee43d8a447cb77977ed", + "gitDir": "test/corpus/repos/javascript", + "sha2": "38ed00f0237ad854471e13f9a859abf746712590" +} +,{ + "testCaseDescription": "javascript-if-else-delete-rest-test", + "expectedResult": { + "changes": { + "if-else.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "if-else.js", + "end": [ + 1, + 29 + ] + } + }, + "summary": "Deleted the 'a' if statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "if-else.js" + ], + "sha1": "38ed00f0237ad854471e13f9a859abf746712590", + "gitDir": "test/corpus/repos/javascript", + "sha2": "8626ab02829f07b2f15f25da58eb41b69afd53e3" +}] diff --git a/test/corpus/diff-summaries/javascript/if.json b/test/corpus/diff-summaries/javascript/if.json new file mode 100644 index 000000000..1568c2e60 --- /dev/null +++ b/test/corpus/diff-summaries/javascript/if.json @@ -0,0 +1,308 @@ +[{ + "testCaseDescription": "javascript-if-insert-test", + "expectedResult": { + "changes": { + "if.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "if.js", + "end": [ + 1, + 19 + ] + } + }, + "summary": "Added the 'x' if statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "if.js" + ], + "sha1": "1fbd44cbdd925bb727f5b07af974a37db31b3ea0", + "gitDir": "test/corpus/repos/javascript", + "sha2": "d2f31345bd3ceb057e9864e3065517bd59d81e84" +} +,{ + "testCaseDescription": "javascript-if-replacement-insert-test", + "expectedResult": { + "changes": { + "if.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "if.js", + "end": [ + 1, + 24 + ] + } + }, + "summary": "Added the 'a.b' if statement", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "if.js", + "end": [ + 2, + 19 + ] + } + }, + "summary": "Added the 'x' if statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "if.js" + ], + "sha1": "d2f31345bd3ceb057e9864e3065517bd59d81e84", + "gitDir": "test/corpus/repos/javascript", + "sha2": "672d891ad62294fecaa1cb0fa0b001748053a2a7" +} +,{ + "testCaseDescription": "javascript-if-delete-insert-test", + "expectedResult": { + "changes": { + "if.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 1 + ], + "name": "if.js", + "end": [ + 1, + 24 + ] + }, + { + "start": [ + 1, + 1 + ], + "name": "if.js", + "end": [ + 1, + 19 + ] + } + ] + }, + "summary": "Replaced the 'a.b' if statement with the 'x' if statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "if.js" + ], + "sha1": "672d891ad62294fecaa1cb0fa0b001748053a2a7", + "gitDir": "test/corpus/repos/javascript", + "sha2": "9a4763d83b29a8834a92126f6c9488397a34ca60" +} +,{ + "testCaseDescription": "javascript-if-replacement-test", + "expectedResult": { + "changes": { + "if.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 1 + ], + "name": "if.js", + "end": [ + 1, + 19 + ] + }, + { + "start": [ + 1, + 1 + ], + "name": "if.js", + "end": [ + 1, + 24 + ] + } + ] + }, + "summary": "Replaced the 'x' if statement with the 'a.b' if statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "if.js" + ], + "sha1": "9a4763d83b29a8834a92126f6c9488397a34ca60", + "gitDir": "test/corpus/repos/javascript", + "sha2": "6fd20d99b1748aff8d5e068f799e9e8c4b174986" +} +,{ + "testCaseDescription": "javascript-if-delete-replacement-test", + "expectedResult": { + "changes": { + "if.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "if.js", + "end": [ + 1, + 24 + ] + } + }, + "summary": "Deleted the 'a.b' if statement", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 1 + ], + "name": "if.js", + "end": [ + 2, + 19 + ] + } + }, + "summary": "Deleted the 'x' if statement", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "if.js", + "end": [ + 2, + 24 + ] + } + }, + "summary": "Added the 'a.b' if statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "if.js" + ], + "sha1": "6fd20d99b1748aff8d5e068f799e9e8c4b174986", + "gitDir": "test/corpus/repos/javascript", + "sha2": "39e72b13348c108e810fea6c43852c082feb83e6" +} +,{ + "testCaseDescription": "javascript-if-delete-test", + "expectedResult": { + "changes": { + "if.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "if.js", + "end": [ + 1, + 19 + ] + } + }, + "summary": "Deleted the 'x' if statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "if.js" + ], + "sha1": "39e72b13348c108e810fea6c43852c082feb83e6", + "gitDir": "test/corpus/repos/javascript", + "sha2": "6bd2aa7a9a559c032a228e8efe94ba3088432ad5" +} +,{ + "testCaseDescription": "javascript-if-delete-rest-test", + "expectedResult": { + "changes": { + "if.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "if.js", + "end": [ + 1, + 24 + ] + } + }, + "summary": "Deleted the 'a.b' if statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "if.js" + ], + "sha1": "6bd2aa7a9a559c032a228e8efe94ba3088432ad5", + "gitDir": "test/corpus/repos/javascript", + "sha2": "a6070e9c94930a94f1913e69bef6da80923cbfde" +}] diff --git a/test/corpus/diff-summaries/javascript/math-assignment-operator.json b/test/corpus/diff-summaries/javascript/math-assignment-operator.json new file mode 100644 index 000000000..d0691c8a7 --- /dev/null +++ b/test/corpus/diff-summaries/javascript/math-assignment-operator.json @@ -0,0 +1,308 @@ +[{ + "testCaseDescription": "javascript-math-assignment-operator-insert-test", + "expectedResult": { + "changes": { + "math-assignment-operator.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "math-assignment-operator.js", + "end": [ + 1, + 7 + ] + } + }, + "summary": "Added the 'x' math assignment", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "math-assignment-operator.js" + ], + "sha1": "de1bc70d66645688aab217b87e9d472a34e42bd1", + "gitDir": "test/corpus/repos/javascript", + "sha2": "304dfd62cf86a774d5233356d3fbf6b8ae6a653f" +} +,{ + "testCaseDescription": "javascript-math-assignment-operator-replacement-insert-test", + "expectedResult": { + "changes": { + "math-assignment-operator.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "math-assignment-operator.js", + "end": [ + 1, + 7 + ] + } + }, + "summary": "Added the 'x' math assignment", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "math-assignment-operator.js", + "end": [ + 2, + 7 + ] + } + }, + "summary": "Added the 'x' math assignment", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "math-assignment-operator.js" + ], + "sha1": "304dfd62cf86a774d5233356d3fbf6b8ae6a653f", + "gitDir": "test/corpus/repos/javascript", + "sha2": "6f518ab031fdda3308872804c6fe6e05a6a188b1" +} +,{ + "testCaseDescription": "javascript-math-assignment-operator-delete-insert-test", + "expectedResult": { + "changes": { + "math-assignment-operator.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 6 + ], + "name": "math-assignment-operator.js", + "end": [ + 1, + 7 + ] + }, + { + "start": [ + 1, + 6 + ], + "name": "math-assignment-operator.js", + "end": [ + 1, + 7 + ] + } + ] + }, + "summary": "Replaced '2' with '1' in the x math assignment", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "math-assignment-operator.js" + ], + "sha1": "6f518ab031fdda3308872804c6fe6e05a6a188b1", + "gitDir": "test/corpus/repos/javascript", + "sha2": "424e6c93d8ff04eed06cec05810e174a8ef07fae" +} +,{ + "testCaseDescription": "javascript-math-assignment-operator-replacement-test", + "expectedResult": { + "changes": { + "math-assignment-operator.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 6 + ], + "name": "math-assignment-operator.js", + "end": [ + 1, + 7 + ] + }, + { + "start": [ + 1, + 6 + ], + "name": "math-assignment-operator.js", + "end": [ + 1, + 7 + ] + } + ] + }, + "summary": "Replaced '1' with '2' in the x math assignment", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "math-assignment-operator.js" + ], + "sha1": "424e6c93d8ff04eed06cec05810e174a8ef07fae", + "gitDir": "test/corpus/repos/javascript", + "sha2": "4ea476b11bab26e33537bcd43da82be1b1329260" +} +,{ + "testCaseDescription": "javascript-math-assignment-operator-delete-replacement-test", + "expectedResult": { + "changes": { + "math-assignment-operator.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "math-assignment-operator.js", + "end": [ + 1, + 7 + ] + } + }, + "summary": "Deleted the 'x' math assignment", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 1 + ], + "name": "math-assignment-operator.js", + "end": [ + 2, + 7 + ] + } + }, + "summary": "Deleted the 'x' math assignment", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "math-assignment-operator.js", + "end": [ + 2, + 7 + ] + } + }, + "summary": "Added the 'x' math assignment", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "math-assignment-operator.js" + ], + "sha1": "4ea476b11bab26e33537bcd43da82be1b1329260", + "gitDir": "test/corpus/repos/javascript", + "sha2": "de5800f3db0450576b6b04eda1bbc145c460e524" +} +,{ + "testCaseDescription": "javascript-math-assignment-operator-delete-test", + "expectedResult": { + "changes": { + "math-assignment-operator.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "math-assignment-operator.js", + "end": [ + 1, + 7 + ] + } + }, + "summary": "Deleted the 'x' math assignment", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "math-assignment-operator.js" + ], + "sha1": "de5800f3db0450576b6b04eda1bbc145c460e524", + "gitDir": "test/corpus/repos/javascript", + "sha2": "02b55a24fd347df4ba80d54a05681ad92de48eae" +} +,{ + "testCaseDescription": "javascript-math-assignment-operator-delete-rest-test", + "expectedResult": { + "changes": { + "math-assignment-operator.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "math-assignment-operator.js", + "end": [ + 1, + 7 + ] + } + }, + "summary": "Deleted the 'x' math assignment", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "math-assignment-operator.js" + ], + "sha1": "02b55a24fd347df4ba80d54a05681ad92de48eae", + "gitDir": "test/corpus/repos/javascript", + "sha2": "1b5320f27fdf477cf7624573d5a594035788a73a" +}] diff --git a/test/corpus/diff-summaries/javascript/math-operator.json b/test/corpus/diff-summaries/javascript/math-operator.json new file mode 100644 index 000000000..f97625053 --- /dev/null +++ b/test/corpus/diff-summaries/javascript/math-operator.json @@ -0,0 +1,368 @@ +[{ + "testCaseDescription": "javascript-math-operator-insert-test", + "expectedResult": { + "changes": { + "math-operator.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "math-operator.js", + "end": [ + 1, + 18 + ] + } + }, + "summary": "Added the 'i + j * 3 - j % 5' math operator", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "math-operator.js" + ], + "sha1": "31ae73e147d1cd8cf95cfdf871344f18fdc91fa2", + "gitDir": "test/corpus/repos/javascript", + "sha2": "f8be46c403f576d3c18c1f3815f7480443755610" +} +,{ + "testCaseDescription": "javascript-math-operator-replacement-insert-test", + "expectedResult": { + "changes": { + "math-operator.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "math-operator.js", + "end": [ + 1, + 18 + ] + } + }, + "summary": "Added the 'i + j * 2 - j % 4' math operator", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "math-operator.js", + "end": [ + 2, + 18 + ] + } + }, + "summary": "Added the 'i + j * 3 - j % 5' math operator", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "math-operator.js" + ], + "sha1": "f8be46c403f576d3c18c1f3815f7480443755610", + "gitDir": "test/corpus/repos/javascript", + "sha2": "2e407188cd18f565b68b11613a8dce6cb8400b1a" +} +,{ + "testCaseDescription": "javascript-math-operator-delete-insert-test", + "expectedResult": { + "changes": { + "math-operator.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 9 + ], + "name": "math-operator.js", + "end": [ + 1, + 10 + ] + }, + { + "start": [ + 1, + 9 + ], + "name": "math-operator.js", + "end": [ + 1, + 10 + ] + } + ] + }, + "summary": "Replaced '2' with '3'", + "tag": "JSONSummary" + }, + { + "span": { + "these": [ + { + "start": [ + 1, + 17 + ], + "name": "math-operator.js", + "end": [ + 1, + 18 + ] + }, + { + "start": [ + 1, + 17 + ], + "name": "math-operator.js", + "end": [ + 1, + 18 + ] + } + ] + }, + "summary": "Replaced '4' with '5'", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "math-operator.js" + ], + "sha1": "2e407188cd18f565b68b11613a8dce6cb8400b1a", + "gitDir": "test/corpus/repos/javascript", + "sha2": "80659409cc4250f823846584dc62802c9a1e6c01" +} +,{ + "testCaseDescription": "javascript-math-operator-replacement-test", + "expectedResult": { + "changes": { + "math-operator.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 9 + ], + "name": "math-operator.js", + "end": [ + 1, + 10 + ] + }, + { + "start": [ + 1, + 9 + ], + "name": "math-operator.js", + "end": [ + 1, + 10 + ] + } + ] + }, + "summary": "Replaced '3' with '2'", + "tag": "JSONSummary" + }, + { + "span": { + "these": [ + { + "start": [ + 1, + 17 + ], + "name": "math-operator.js", + "end": [ + 1, + 18 + ] + }, + { + "start": [ + 1, + 17 + ], + "name": "math-operator.js", + "end": [ + 1, + 18 + ] + } + ] + }, + "summary": "Replaced '5' with '4'", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "math-operator.js" + ], + "sha1": "80659409cc4250f823846584dc62802c9a1e6c01", + "gitDir": "test/corpus/repos/javascript", + "sha2": "f1878a2a74738ad67fb08d40334f351d4238e023" +} +,{ + "testCaseDescription": "javascript-math-operator-delete-replacement-test", + "expectedResult": { + "changes": { + "math-operator.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "math-operator.js", + "end": [ + 1, + 18 + ] + } + }, + "summary": "Deleted the 'i + j * 2 - j % 4' math operator", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 1 + ], + "name": "math-operator.js", + "end": [ + 2, + 18 + ] + } + }, + "summary": "Deleted the 'i + j * 3 - j % 5' math operator", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "math-operator.js", + "end": [ + 2, + 18 + ] + } + }, + "summary": "Added the 'i + j * 2 - j % 4' math operator", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "math-operator.js" + ], + "sha1": "f1878a2a74738ad67fb08d40334f351d4238e023", + "gitDir": "test/corpus/repos/javascript", + "sha2": "2eb48e213a12b09d764a5f58eec7d90985a9c66c" +} +,{ + "testCaseDescription": "javascript-math-operator-delete-test", + "expectedResult": { + "changes": { + "math-operator.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "math-operator.js", + "end": [ + 1, + 18 + ] + } + }, + "summary": "Deleted the 'i + j * 3 - j % 5' math operator", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "math-operator.js" + ], + "sha1": "2eb48e213a12b09d764a5f58eec7d90985a9c66c", + "gitDir": "test/corpus/repos/javascript", + "sha2": "e653a346a34e6374ab80a527dbbb777ec05f986c" +} +,{ + "testCaseDescription": "javascript-math-operator-delete-rest-test", + "expectedResult": { + "changes": { + "math-operator.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "math-operator.js", + "end": [ + 1, + 18 + ] + } + }, + "summary": "Deleted the 'i + j * 2 - j % 4' math operator", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "math-operator.js" + ], + "sha1": "e653a346a34e6374ab80a527dbbb777ec05f986c", + "gitDir": "test/corpus/repos/javascript", + "sha2": "cb37f95870629005756c374dade2599850dc09d3" +}] diff --git a/test/corpus/diff-summaries/javascript/member-access-assignment.json b/test/corpus/diff-summaries/javascript/member-access-assignment.json new file mode 100644 index 000000000..35333c4b5 --- /dev/null +++ b/test/corpus/diff-summaries/javascript/member-access-assignment.json @@ -0,0 +1,308 @@ +[{ + "testCaseDescription": "javascript-member-access-assignment-insert-test", + "expectedResult": { + "changes": { + "member-access-assignment.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "member-access-assignment.js", + "end": [ + 1, + 8 + ] + } + }, + "summary": "Added the 'y.x' assignment", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "member-access-assignment.js" + ], + "sha1": "6882106e2e1564145c50f664a6446f6c37b1ab3f", + "gitDir": "test/corpus/repos/javascript", + "sha2": "e25f5c9031b1c4881133070ab71fd755d165ead5" +} +,{ + "testCaseDescription": "javascript-member-access-assignment-replacement-insert-test", + "expectedResult": { + "changes": { + "member-access-assignment.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "member-access-assignment.js", + "end": [ + 1, + 8 + ] + } + }, + "summary": "Added the 'y.x' assignment", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "member-access-assignment.js", + "end": [ + 2, + 8 + ] + } + }, + "summary": "Added the 'y.x' assignment", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "member-access-assignment.js" + ], + "sha1": "e25f5c9031b1c4881133070ab71fd755d165ead5", + "gitDir": "test/corpus/repos/javascript", + "sha2": "9d9f04beab9f8d927ddbf0d4939d5651055d1577" +} +,{ + "testCaseDescription": "javascript-member-access-assignment-delete-insert-test", + "expectedResult": { + "changes": { + "member-access-assignment.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 7 + ], + "name": "member-access-assignment.js", + "end": [ + 1, + 8 + ] + }, + { + "start": [ + 1, + 7 + ], + "name": "member-access-assignment.js", + "end": [ + 1, + 8 + ] + } + ] + }, + "summary": "Replaced '1' with '0' in an assignment to y.x", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "member-access-assignment.js" + ], + "sha1": "9d9f04beab9f8d927ddbf0d4939d5651055d1577", + "gitDir": "test/corpus/repos/javascript", + "sha2": "bb31011c60ec572395dbe73bb48dd13be1cd6bb3" +} +,{ + "testCaseDescription": "javascript-member-access-assignment-replacement-test", + "expectedResult": { + "changes": { + "member-access-assignment.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 7 + ], + "name": "member-access-assignment.js", + "end": [ + 1, + 8 + ] + }, + { + "start": [ + 1, + 7 + ], + "name": "member-access-assignment.js", + "end": [ + 1, + 8 + ] + } + ] + }, + "summary": "Replaced '0' with '1' in an assignment to y.x", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "member-access-assignment.js" + ], + "sha1": "bb31011c60ec572395dbe73bb48dd13be1cd6bb3", + "gitDir": "test/corpus/repos/javascript", + "sha2": "7706b38694acad8dd246351a7623409cf63685ae" +} +,{ + "testCaseDescription": "javascript-member-access-assignment-delete-replacement-test", + "expectedResult": { + "changes": { + "member-access-assignment.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "member-access-assignment.js", + "end": [ + 1, + 8 + ] + } + }, + "summary": "Deleted the 'y.x' assignment", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 1 + ], + "name": "member-access-assignment.js", + "end": [ + 2, + 8 + ] + } + }, + "summary": "Deleted the 'y.x' assignment", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "member-access-assignment.js", + "end": [ + 2, + 8 + ] + } + }, + "summary": "Added the 'y.x' assignment", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "member-access-assignment.js" + ], + "sha1": "7706b38694acad8dd246351a7623409cf63685ae", + "gitDir": "test/corpus/repos/javascript", + "sha2": "75dcf600f84cc516ba6e606ae623217e558da992" +} +,{ + "testCaseDescription": "javascript-member-access-assignment-delete-test", + "expectedResult": { + "changes": { + "member-access-assignment.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "member-access-assignment.js", + "end": [ + 1, + 8 + ] + } + }, + "summary": "Deleted the 'y.x' assignment", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "member-access-assignment.js" + ], + "sha1": "75dcf600f84cc516ba6e606ae623217e558da992", + "gitDir": "test/corpus/repos/javascript", + "sha2": "003aa769197d4440824e267b4cc77c0f57a73561" +} +,{ + "testCaseDescription": "javascript-member-access-assignment-delete-rest-test", + "expectedResult": { + "changes": { + "member-access-assignment.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "member-access-assignment.js", + "end": [ + 1, + 8 + ] + } + }, + "summary": "Deleted the 'y.x' assignment", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "member-access-assignment.js" + ], + "sha1": "003aa769197d4440824e267b4cc77c0f57a73561", + "gitDir": "test/corpus/repos/javascript", + "sha2": "9b3e79687880bf10eac28404f1b0de7e74e0ba44" +}] diff --git a/test/corpus/diff-summaries/javascript/member-access.json b/test/corpus/diff-summaries/javascript/member-access.json new file mode 100644 index 000000000..9983d56f3 --- /dev/null +++ b/test/corpus/diff-summaries/javascript/member-access.json @@ -0,0 +1,308 @@ +[{ + "testCaseDescription": "javascript-member-access-insert-test", + "expectedResult": { + "changes": { + "member-access.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "member-access.js", + "end": [ + 1, + 15 + ] + } + }, + "summary": "Added the 'x.someProperty' member access", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "member-access.js" + ], + "sha1": "fac60fda4353135fc163df6a61e7caff13930fc7", + "gitDir": "test/corpus/repos/javascript", + "sha2": "b850815e1453fa74ddb093149a5dfef236567c8d" +} +,{ + "testCaseDescription": "javascript-member-access-replacement-insert-test", + "expectedResult": { + "changes": { + "member-access.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "member-access.js", + "end": [ + 1, + 20 + ] + } + }, + "summary": "Added the 'x.someOtherProperty' member access", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "member-access.js", + "end": [ + 2, + 15 + ] + } + }, + "summary": "Added the 'x.someProperty' member access", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "member-access.js" + ], + "sha1": "b850815e1453fa74ddb093149a5dfef236567c8d", + "gitDir": "test/corpus/repos/javascript", + "sha2": "3a70c4b8bb055fd5a22da6919300d8f980d02a6c" +} +,{ + "testCaseDescription": "javascript-member-access-delete-insert-test", + "expectedResult": { + "changes": { + "member-access.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 3 + ], + "name": "member-access.js", + "end": [ + 1, + 20 + ] + }, + { + "start": [ + 1, + 3 + ], + "name": "member-access.js", + "end": [ + 1, + 15 + ] + } + ] + }, + "summary": "Replaced the 'someOtherProperty' identifier with the 'someProperty' identifier", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "member-access.js" + ], + "sha1": "3a70c4b8bb055fd5a22da6919300d8f980d02a6c", + "gitDir": "test/corpus/repos/javascript", + "sha2": "f60cc2bbbedaacb8eb700f1a3bda7b06275a8d27" +} +,{ + "testCaseDescription": "javascript-member-access-replacement-test", + "expectedResult": { + "changes": { + "member-access.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 3 + ], + "name": "member-access.js", + "end": [ + 1, + 15 + ] + }, + { + "start": [ + 1, + 3 + ], + "name": "member-access.js", + "end": [ + 1, + 20 + ] + } + ] + }, + "summary": "Replaced the 'someProperty' identifier with the 'someOtherProperty' identifier", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "member-access.js" + ], + "sha1": "f60cc2bbbedaacb8eb700f1a3bda7b06275a8d27", + "gitDir": "test/corpus/repos/javascript", + "sha2": "0663adbbe511b93eda40866fe376618cae48678d" +} +,{ + "testCaseDescription": "javascript-member-access-delete-replacement-test", + "expectedResult": { + "changes": { + "member-access.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "member-access.js", + "end": [ + 1, + 20 + ] + } + }, + "summary": "Deleted the 'x.someOtherProperty' member access", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 1 + ], + "name": "member-access.js", + "end": [ + 2, + 15 + ] + } + }, + "summary": "Deleted the 'x.someProperty' member access", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "member-access.js", + "end": [ + 2, + 20 + ] + } + }, + "summary": "Added the 'x.someOtherProperty' member access", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "member-access.js" + ], + "sha1": "0663adbbe511b93eda40866fe376618cae48678d", + "gitDir": "test/corpus/repos/javascript", + "sha2": "837649081bbf641849fbc2d53224894bd8678f0b" +} +,{ + "testCaseDescription": "javascript-member-access-delete-test", + "expectedResult": { + "changes": { + "member-access.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "member-access.js", + "end": [ + 1, + 15 + ] + } + }, + "summary": "Deleted the 'x.someProperty' member access", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "member-access.js" + ], + "sha1": "837649081bbf641849fbc2d53224894bd8678f0b", + "gitDir": "test/corpus/repos/javascript", + "sha2": "34eac603f132671867cb2457bb017ee2583a1d54" +} +,{ + "testCaseDescription": "javascript-member-access-delete-rest-test", + "expectedResult": { + "changes": { + "member-access.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "member-access.js", + "end": [ + 1, + 20 + ] + } + }, + "summary": "Deleted the 'x.someOtherProperty' member access", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "member-access.js" + ], + "sha1": "34eac603f132671867cb2457bb017ee2583a1d54", + "gitDir": "test/corpus/repos/javascript", + "sha2": "c11043ad084bd837ff463621da19892d2cc68719" +}] diff --git a/test/corpus/diff-summaries/javascript/method-call.json b/test/corpus/diff-summaries/javascript/method-call.json new file mode 100644 index 000000000..c36706a75 --- /dev/null +++ b/test/corpus/diff-summaries/javascript/method-call.json @@ -0,0 +1,308 @@ +[{ + "testCaseDescription": "javascript-method-call-insert-test", + "expectedResult": { + "changes": { + "method-call.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "method-call.js", + "end": [ + 1, + 32 + ] + } + }, + "summary": "Added the 'object.someMethod(arg1, \"arg2\")' method call", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "method-call.js" + ], + "sha1": "bde44008cfb326f395ddb1071a073fc1113ffb3d", + "gitDir": "test/corpus/repos/javascript", + "sha2": "80d9e1c3f364424fd85eb3ee59e8790187596cba" +} +,{ + "testCaseDescription": "javascript-method-call-replacement-insert-test", + "expectedResult": { + "changes": { + "method-call.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "method-call.js", + "end": [ + 1, + 32 + ] + } + }, + "summary": "Added the 'object.someMethod(arg1, \"arg3\")' method call", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "method-call.js", + "end": [ + 2, + 32 + ] + } + }, + "summary": "Added the 'object.someMethod(arg1, \"arg2\")' method call", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "method-call.js" + ], + "sha1": "80d9e1c3f364424fd85eb3ee59e8790187596cba", + "gitDir": "test/corpus/repos/javascript", + "sha2": "d3da8ea868cfb41cfd38f8264933c2b7271c7734" +} +,{ + "testCaseDescription": "javascript-method-call-delete-insert-test", + "expectedResult": { + "changes": { + "method-call.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 25 + ], + "name": "method-call.js", + "end": [ + 1, + 31 + ] + }, + { + "start": [ + 1, + 25 + ], + "name": "method-call.js", + "end": [ + 1, + 31 + ] + } + ] + }, + "summary": "Replaced the \"arg3\" string with the \"arg2\" string in the object.someMethod(arg1, \"arg2\") method call", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "method-call.js" + ], + "sha1": "d3da8ea868cfb41cfd38f8264933c2b7271c7734", + "gitDir": "test/corpus/repos/javascript", + "sha2": "262dfb0009e74472f2064911509300f17714002d" +} +,{ + "testCaseDescription": "javascript-method-call-replacement-test", + "expectedResult": { + "changes": { + "method-call.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 25 + ], + "name": "method-call.js", + "end": [ + 1, + 31 + ] + }, + { + "start": [ + 1, + 25 + ], + "name": "method-call.js", + "end": [ + 1, + 31 + ] + } + ] + }, + "summary": "Replaced the \"arg2\" string with the \"arg3\" string in the object.someMethod(arg1, \"arg3\") method call", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "method-call.js" + ], + "sha1": "262dfb0009e74472f2064911509300f17714002d", + "gitDir": "test/corpus/repos/javascript", + "sha2": "6be53135abf6f6b89c6111798030e91721826c59" +} +,{ + "testCaseDescription": "javascript-method-call-delete-replacement-test", + "expectedResult": { + "changes": { + "method-call.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "method-call.js", + "end": [ + 1, + 32 + ] + } + }, + "summary": "Deleted the 'object.someMethod(arg1, \"arg3\")' method call", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 1 + ], + "name": "method-call.js", + "end": [ + 2, + 32 + ] + } + }, + "summary": "Deleted the 'object.someMethod(arg1, \"arg2\")' method call", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "method-call.js", + "end": [ + 2, + 32 + ] + } + }, + "summary": "Added the 'object.someMethod(arg1, \"arg3\")' method call", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "method-call.js" + ], + "sha1": "6be53135abf6f6b89c6111798030e91721826c59", + "gitDir": "test/corpus/repos/javascript", + "sha2": "ee8b6a26e5f54845b632bdbf0543d81b6da15700" +} +,{ + "testCaseDescription": "javascript-method-call-delete-test", + "expectedResult": { + "changes": { + "method-call.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "method-call.js", + "end": [ + 1, + 32 + ] + } + }, + "summary": "Deleted the 'object.someMethod(arg1, \"arg2\")' method call", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "method-call.js" + ], + "sha1": "ee8b6a26e5f54845b632bdbf0543d81b6da15700", + "gitDir": "test/corpus/repos/javascript", + "sha2": "1129af20d307473ea4e2d4d577ea53c7bdaed636" +} +,{ + "testCaseDescription": "javascript-method-call-delete-rest-test", + "expectedResult": { + "changes": { + "method-call.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "method-call.js", + "end": [ + 1, + 32 + ] + } + }, + "summary": "Deleted the 'object.someMethod(arg1, \"arg3\")' method call", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "method-call.js" + ], + "sha1": "1129af20d307473ea4e2d4d577ea53c7bdaed636", + "gitDir": "test/corpus/repos/javascript", + "sha2": "7a9cdc6c356ec1e7fe6e47c923898d3e2e6a32cc" +}] diff --git a/test/corpus/diff-summaries/javascript/named-function.json b/test/corpus/diff-summaries/javascript/named-function.json new file mode 100644 index 000000000..c03cd9f4f --- /dev/null +++ b/test/corpus/diff-summaries/javascript/named-function.json @@ -0,0 +1,444 @@ +[{ + "testCaseDescription": "javascript-named-function-insert-test", + "expectedResult": { + "changes": { + "named-function.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "named-function.js", + "end": [ + 1, + 42 + ] + } + }, + "summary": "Added the 'myFunction' function", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "named-function.js" + ], + "sha1": "5fe4477fe4c9d164946d8aaf8fe66f107b0901b4", + "gitDir": "test/corpus/repos/javascript", + "sha2": "c86bb45b4e0f5b90e2ea9a371df0026ac6b147ca" +} +,{ + "testCaseDescription": "javascript-named-function-replacement-insert-test", + "expectedResult": { + "changes": { + "named-function.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "named-function.js", + "end": [ + 1, + 45 + ] + } + }, + "summary": "Added the 'anotherFunction' function", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "named-function.js", + "end": [ + 2, + 42 + ] + } + }, + "summary": "Added the 'myFunction' function", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "named-function.js" + ], + "sha1": "c86bb45b4e0f5b90e2ea9a371df0026ac6b147ca", + "gitDir": "test/corpus/repos/javascript", + "sha2": "370e7dcd8b0e49fa442f84396ad081ec1e61657e" +} +,{ + "testCaseDescription": "javascript-named-function-delete-insert-test", + "expectedResult": { + "changes": { + "named-function.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 10 + ], + "name": "named-function.js", + "end": [ + 1, + 25 + ] + }, + { + "start": [ + 1, + 10 + ], + "name": "named-function.js", + "end": [ + 1, + 20 + ] + } + ] + }, + "summary": "Replaced the 'anotherFunction' identifier with the 'myFunction' identifier in the myFunction function", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 1, + 21 + ], + "name": "named-function.js", + "end": [ + 1, + 25 + ] + } + }, + "summary": "Added the 'arg1' identifier in the myFunction function", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 1, + 27 + ], + "name": "named-function.js", + "end": [ + 1, + 31 + ] + } + }, + "summary": "Added the 'arg2' identifier in the myFunction function", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 1, + 35 + ], + "name": "named-function.js", + "end": [ + 1, + 39 + ] + } + }, + "summary": "Added the 'arg2' identifier in the myFunction function", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 1, + 30 + ], + "name": "named-function.js", + "end": [ + 1, + 43 + ] + } + }, + "summary": "Deleted the 'false' return statement in the myFunction function", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "named-function.js" + ], + "sha1": "370e7dcd8b0e49fa442f84396ad081ec1e61657e", + "gitDir": "test/corpus/repos/javascript", + "sha2": "3f231c35b4a10a3e3e2188bc377e56d1de4d67ca" +} +,{ + "testCaseDescription": "javascript-named-function-replacement-test", + "expectedResult": { + "changes": { + "named-function.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 10 + ], + "name": "named-function.js", + "end": [ + 1, + 20 + ] + }, + { + "start": [ + 1, + 10 + ], + "name": "named-function.js", + "end": [ + 1, + 25 + ] + } + ] + }, + "summary": "Replaced the 'myFunction' identifier with the 'anotherFunction' identifier in the anotherFunction function", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 1, + 21 + ], + "name": "named-function.js", + "end": [ + 1, + 25 + ] + } + }, + "summary": "Deleted the 'arg1' identifier in the anotherFunction function", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 1, + 27 + ], + "name": "named-function.js", + "end": [ + 1, + 31 + ] + } + }, + "summary": "Deleted the 'arg2' identifier in the anotherFunction function", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 1, + 30 + ], + "name": "named-function.js", + "end": [ + 1, + 43 + ] + } + }, + "summary": "Added the 'false' return statement in the anotherFunction function", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 1, + 35 + ], + "name": "named-function.js", + "end": [ + 1, + 39 + ] + } + }, + "summary": "Deleted the 'arg2' identifier in the anotherFunction function", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "named-function.js" + ], + "sha1": "3f231c35b4a10a3e3e2188bc377e56d1de4d67ca", + "gitDir": "test/corpus/repos/javascript", + "sha2": "f51128e06754269e3518efb3c37bfb93dde1e6e3" +} +,{ + "testCaseDescription": "javascript-named-function-delete-replacement-test", + "expectedResult": { + "changes": { + "named-function.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "named-function.js", + "end": [ + 1, + 45 + ] + } + }, + "summary": "Deleted the 'anotherFunction' function", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 1 + ], + "name": "named-function.js", + "end": [ + 2, + 42 + ] + } + }, + "summary": "Deleted the 'myFunction' function", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "named-function.js", + "end": [ + 2, + 45 + ] + } + }, + "summary": "Added the 'anotherFunction' function", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "named-function.js" + ], + "sha1": "f51128e06754269e3518efb3c37bfb93dde1e6e3", + "gitDir": "test/corpus/repos/javascript", + "sha2": "79a5f19ec8642f46ea2c6525df20c26fd2ca9cfc" +} +,{ + "testCaseDescription": "javascript-named-function-delete-test", + "expectedResult": { + "changes": { + "named-function.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "named-function.js", + "end": [ + 1, + 42 + ] + } + }, + "summary": "Deleted the 'myFunction' function", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "named-function.js" + ], + "sha1": "79a5f19ec8642f46ea2c6525df20c26fd2ca9cfc", + "gitDir": "test/corpus/repos/javascript", + "sha2": "1e9c6be37ab1267bf448d0475d8db90a8e60afd1" +} +,{ + "testCaseDescription": "javascript-named-function-delete-rest-test", + "expectedResult": { + "changes": { + "named-function.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "named-function.js", + "end": [ + 1, + 45 + ] + } + }, + "summary": "Deleted the 'anotherFunction' function", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "named-function.js" + ], + "sha1": "1e9c6be37ab1267bf448d0475d8db90a8e60afd1", + "gitDir": "test/corpus/repos/javascript", + "sha2": "fac60fda4353135fc163df6a61e7caff13930fc7" +}] diff --git a/test/corpus/diff-summaries/javascript/nested-functions.json b/test/corpus/diff-summaries/javascript/nested-functions.json new file mode 100644 index 000000000..8f8b95b35 --- /dev/null +++ b/test/corpus/diff-summaries/javascript/nested-functions.json @@ -0,0 +1,368 @@ +[{ + "testCaseDescription": "javascript-nested-functions-insert-test", + "expectedResult": { + "changes": { + "nested-functions.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "nested-functions.js", + "end": [ + 1, + 103 + ] + } + }, + "summary": "Added the 'parent' function", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "nested-functions.js" + ], + "sha1": "1ad3455503bfb6621a6b418f015349c2bd2a957d", + "gitDir": "test/corpus/repos/javascript", + "sha2": "a895199ca338b56967e3a62869616c333b677551" +} +,{ + "testCaseDescription": "javascript-nested-functions-replacement-insert-test", + "expectedResult": { + "changes": { + "nested-functions.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "nested-functions.js", + "end": [ + 1, + 103 + ] + } + }, + "summary": "Added the 'parent' function", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "nested-functions.js", + "end": [ + 2, + 103 + ] + } + }, + "summary": "Added the 'parent' function", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "nested-functions.js" + ], + "sha1": "a895199ca338b56967e3a62869616c333b677551", + "gitDir": "test/corpus/repos/javascript", + "sha2": "801ab172957b72d8babcda5c151b009325b97d46" +} +,{ + "testCaseDescription": "javascript-nested-functions-delete-insert-test", + "expectedResult": { + "changes": { + "nested-functions.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 74 + ], + "name": "nested-functions.js", + "end": [ + 1, + 78 + ] + }, + { + "start": [ + 1, + 74 + ], + "name": "nested-functions.js", + "end": [ + 1, + 78 + ] + } + ] + }, + "summary": "Replaced the 'arg1' identifier with the 'arg3' identifier in the console.log(arg3) method call of the 'child' function", + "tag": "JSONSummary" + }, + { + "span": { + "these": [ + { + "start": [ + 1, + 93 + ], + "name": "nested-functions.js", + "end": [ + 1, + 97 + ] + }, + { + "start": [ + 1, + 93 + ], + "name": "nested-functions.js", + "end": [ + 1, + 97 + ] + } + ] + }, + "summary": "Replaced the 'arg2' identifier with the 'arg4' identifier in the console.log(arg4) method call of the 'child' function", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "nested-functions.js" + ], + "sha1": "801ab172957b72d8babcda5c151b009325b97d46", + "gitDir": "test/corpus/repos/javascript", + "sha2": "e8b1e1efe706cf565df615f0cd9cc3514881ea82" +} +,{ + "testCaseDescription": "javascript-nested-functions-replacement-test", + "expectedResult": { + "changes": { + "nested-functions.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 74 + ], + "name": "nested-functions.js", + "end": [ + 1, + 78 + ] + }, + { + "start": [ + 1, + 74 + ], + "name": "nested-functions.js", + "end": [ + 1, + 78 + ] + } + ] + }, + "summary": "Replaced the 'arg3' identifier with the 'arg1' identifier in the console.log(arg1) method call of the 'child' function", + "tag": "JSONSummary" + }, + { + "span": { + "these": [ + { + "start": [ + 1, + 93 + ], + "name": "nested-functions.js", + "end": [ + 1, + 97 + ] + }, + { + "start": [ + 1, + 93 + ], + "name": "nested-functions.js", + "end": [ + 1, + 97 + ] + } + ] + }, + "summary": "Replaced the 'arg4' identifier with the 'arg2' identifier in the console.log(arg2) method call of the 'child' function", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "nested-functions.js" + ], + "sha1": "e8b1e1efe706cf565df615f0cd9cc3514881ea82", + "gitDir": "test/corpus/repos/javascript", + "sha2": "50489ea764a308d499766e2c3e0da4215ce5ac34" +} +,{ + "testCaseDescription": "javascript-nested-functions-delete-replacement-test", + "expectedResult": { + "changes": { + "nested-functions.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "nested-functions.js", + "end": [ + 1, + 103 + ] + } + }, + "summary": "Deleted the 'parent' function", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 1 + ], + "name": "nested-functions.js", + "end": [ + 2, + 103 + ] + } + }, + "summary": "Deleted the 'parent' function", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "nested-functions.js", + "end": [ + 2, + 103 + ] + } + }, + "summary": "Added the 'parent' function", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "nested-functions.js" + ], + "sha1": "50489ea764a308d499766e2c3e0da4215ce5ac34", + "gitDir": "test/corpus/repos/javascript", + "sha2": "9d53457b894350de4b09b86914c8dbcc04f999ab" +} +,{ + "testCaseDescription": "javascript-nested-functions-delete-test", + "expectedResult": { + "changes": { + "nested-functions.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "nested-functions.js", + "end": [ + 1, + 103 + ] + } + }, + "summary": "Deleted the 'parent' function", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "nested-functions.js" + ], + "sha1": "9d53457b894350de4b09b86914c8dbcc04f999ab", + "gitDir": "test/corpus/repos/javascript", + "sha2": "4b43d1d5ce4632f57879d9021bae72e01ef78234" +} +,{ + "testCaseDescription": "javascript-nested-functions-delete-rest-test", + "expectedResult": { + "changes": { + "nested-functions.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "nested-functions.js", + "end": [ + 1, + 103 + ] + } + }, + "summary": "Deleted the 'parent' function", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "nested-functions.js" + ], + "sha1": "4b43d1d5ce4632f57879d9021bae72e01ef78234", + "gitDir": "test/corpus/repos/javascript", + "sha2": "6c18f0fbe80bb95f6642653913241b9065181591" +}] diff --git a/test/corpus/diff-summaries/javascript/null.json b/test/corpus/diff-summaries/javascript/null.json new file mode 100644 index 000000000..8290d24e2 --- /dev/null +++ b/test/corpus/diff-summaries/javascript/null.json @@ -0,0 +1,316 @@ +[{ + "testCaseDescription": "javascript-null-insert-test", + "expectedResult": { + "changes": { + "null.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "null.js", + "end": [ + 1, + 5 + ] + } + }, + "summary": "Added the 'null' identifier", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "null.js" + ], + "sha1": "e876cda8f0a6a14bd8518d84e985c6616b2f5548", + "gitDir": "test/corpus/repos/javascript", + "sha2": "7dcac4962ac6c1d7244fa02e89e11d3ea031fa94" +} +,{ + "testCaseDescription": "javascript-null-replacement-insert-test", + "expectedResult": { + "changes": { + "null.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "null.js", + "end": [ + 1, + 13 + ] + } + }, + "summary": "Added the 'null' return statement", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "null.js", + "end": [ + 2, + 5 + ] + } + }, + "summary": "Added the 'null' identifier", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "null.js" + ], + "sha1": "7dcac4962ac6c1d7244fa02e89e11d3ea031fa94", + "gitDir": "test/corpus/repos/javascript", + "sha2": "0562686e9fd41baa86ab32fbeb95bf53e9c55b61" +} +,{ + "testCaseDescription": "javascript-null-delete-insert-test", + "expectedResult": { + "changes": { + "null.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "null.js", + "end": [ + 1, + 5 + ] + } + }, + "summary": "Added the 'null' identifier", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "null.js", + "end": [ + 1, + 13 + ] + } + }, + "summary": "Deleted the 'null' return statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "null.js" + ], + "sha1": "0562686e9fd41baa86ab32fbeb95bf53e9c55b61", + "gitDir": "test/corpus/repos/javascript", + "sha2": "55c2830f73312678a37a376936a88e1c070a9400" +} +,{ + "testCaseDescription": "javascript-null-replacement-test", + "expectedResult": { + "changes": { + "null.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "null.js", + "end": [ + 1, + 13 + ] + } + }, + "summary": "Added the 'null' return statement", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "null.js", + "end": [ + 1, + 5 + ] + } + }, + "summary": "Deleted the 'null' identifier", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "null.js" + ], + "sha1": "55c2830f73312678a37a376936a88e1c070a9400", + "gitDir": "test/corpus/repos/javascript", + "sha2": "c950b4804d1bb4b66757d3d4684b3d3d07dd74ca" +} +,{ + "testCaseDescription": "javascript-null-delete-replacement-test", + "expectedResult": { + "changes": { + "null.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "null.js", + "end": [ + 1, + 13 + ] + } + }, + "summary": "Deleted the 'null' return statement", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 1 + ], + "name": "null.js", + "end": [ + 2, + 5 + ] + } + }, + "summary": "Deleted the 'null' identifier", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "null.js", + "end": [ + 2, + 13 + ] + } + }, + "summary": "Added the 'null' return statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "null.js" + ], + "sha1": "c950b4804d1bb4b66757d3d4684b3d3d07dd74ca", + "gitDir": "test/corpus/repos/javascript", + "sha2": "5b41396ccd34ae1f6813fc4ab6ee6ec65877ae9d" +} +,{ + "testCaseDescription": "javascript-null-delete-test", + "expectedResult": { + "changes": { + "null.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "null.js", + "end": [ + 1, + 5 + ] + } + }, + "summary": "Deleted the 'null' identifier", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "null.js" + ], + "sha1": "5b41396ccd34ae1f6813fc4ab6ee6ec65877ae9d", + "gitDir": "test/corpus/repos/javascript", + "sha2": "926763653ba7397bedb14c053ed3a3ca36df9de3" +} +,{ + "testCaseDescription": "javascript-null-delete-rest-test", + "expectedResult": { + "changes": { + "null.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "null.js", + "end": [ + 1, + 13 + ] + } + }, + "summary": "Deleted the 'null' return statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "null.js" + ], + "sha1": "926763653ba7397bedb14c053ed3a3ca36df9de3", + "gitDir": "test/corpus/repos/javascript", + "sha2": "c4cbb6a4ff71852691d643f686d8231c9a3989a4" +}] diff --git a/test/corpus/diff-summaries/javascript/number.json b/test/corpus/diff-summaries/javascript/number.json new file mode 100644 index 000000000..1fae655a3 --- /dev/null +++ b/test/corpus/diff-summaries/javascript/number.json @@ -0,0 +1,308 @@ +[{ + "testCaseDescription": "javascript-number-insert-test", + "expectedResult": { + "changes": { + "number.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "number.js", + "end": [ + 1, + 4 + ] + } + }, + "summary": "Added '101'", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "number.js" + ], + "sha1": "20b94162d6be612a1c0111cb75ee0f3beadcab6e", + "gitDir": "test/corpus/repos/javascript", + "sha2": "1761ef1d335d09d579cbe1787558398e4f8d264b" +} +,{ + "testCaseDescription": "javascript-number-replacement-insert-test", + "expectedResult": { + "changes": { + "number.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "number.js", + "end": [ + 1, + 4 + ] + } + }, + "summary": "Added '102'", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "number.js", + "end": [ + 2, + 4 + ] + } + }, + "summary": "Added '101'", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "number.js" + ], + "sha1": "1761ef1d335d09d579cbe1787558398e4f8d264b", + "gitDir": "test/corpus/repos/javascript", + "sha2": "6196bff8f4104451020c72765217b3d224951070" +} +,{ + "testCaseDescription": "javascript-number-delete-insert-test", + "expectedResult": { + "changes": { + "number.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 1 + ], + "name": "number.js", + "end": [ + 1, + 4 + ] + }, + { + "start": [ + 1, + 1 + ], + "name": "number.js", + "end": [ + 1, + 4 + ] + } + ] + }, + "summary": "Replaced '102' with '101'", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "number.js" + ], + "sha1": "6196bff8f4104451020c72765217b3d224951070", + "gitDir": "test/corpus/repos/javascript", + "sha2": "dc888e9f5129c85c17924e12d47538ae093853c0" +} +,{ + "testCaseDescription": "javascript-number-replacement-test", + "expectedResult": { + "changes": { + "number.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 1 + ], + "name": "number.js", + "end": [ + 1, + 4 + ] + }, + { + "start": [ + 1, + 1 + ], + "name": "number.js", + "end": [ + 1, + 4 + ] + } + ] + }, + "summary": "Replaced '101' with '102'", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "number.js" + ], + "sha1": "dc888e9f5129c85c17924e12d47538ae093853c0", + "gitDir": "test/corpus/repos/javascript", + "sha2": "ee2939ca49b0baba42dd83ab0361e128c2565d93" +} +,{ + "testCaseDescription": "javascript-number-delete-replacement-test", + "expectedResult": { + "changes": { + "number.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "number.js", + "end": [ + 1, + 4 + ] + } + }, + "summary": "Deleted '102'", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 1 + ], + "name": "number.js", + "end": [ + 2, + 4 + ] + } + }, + "summary": "Deleted '101'", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "number.js", + "end": [ + 2, + 4 + ] + } + }, + "summary": "Added '102'", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "number.js" + ], + "sha1": "ee2939ca49b0baba42dd83ab0361e128c2565d93", + "gitDir": "test/corpus/repos/javascript", + "sha2": "b1fddfc7e3131549e7150bda348f9dddb963efc8" +} +,{ + "testCaseDescription": "javascript-number-delete-test", + "expectedResult": { + "changes": { + "number.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "number.js", + "end": [ + 1, + 4 + ] + } + }, + "summary": "Deleted '101'", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "number.js" + ], + "sha1": "b1fddfc7e3131549e7150bda348f9dddb963efc8", + "gitDir": "test/corpus/repos/javascript", + "sha2": "9bd4606cce2739f6d61c83c3b8045dbdf85874c3" +} +,{ + "testCaseDescription": "javascript-number-delete-rest-test", + "expectedResult": { + "changes": { + "number.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "number.js", + "end": [ + 1, + 4 + ] + } + }, + "summary": "Deleted '102'", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "number.js" + ], + "sha1": "9bd4606cce2739f6d61c83c3b8045dbdf85874c3", + "gitDir": "test/corpus/repos/javascript", + "sha2": "4df21e328803748f18b7cd64862f776a275b1448" +}] diff --git a/test/corpus/diff-summaries/javascript/object-with-methods.json b/test/corpus/diff-summaries/javascript/object-with-methods.json new file mode 100644 index 000000000..4a09bfa0f --- /dev/null +++ b/test/corpus/diff-summaries/javascript/object-with-methods.json @@ -0,0 +1,308 @@ +[{ + "testCaseDescription": "javascript-objects-with-methods-insert-test", + "expectedResult": { + "changes": { + "objects-with-methods.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "objects-with-methods.js", + "end": [ + 1, + 32 + ] + } + }, + "summary": "Added the '{ add }' object", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "objects-with-methods.js" + ], + "sha1": "a7028eef7c56f7ba5c5dda0faadcfffe205d5a40", + "gitDir": "test/corpus/repos/javascript", + "sha2": "3006c2d8134eb46077d39614fdcb4521dbdb0b17" +} +,{ + "testCaseDescription": "javascript-objects-with-methods-replacement-insert-test", + "expectedResult": { + "changes": { + "objects-with-methods.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "objects-with-methods.js", + "end": [ + 1, + 37 + ] + } + }, + "summary": "Added the '{ subtract }' object", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "objects-with-methods.js", + "end": [ + 2, + 32 + ] + } + }, + "summary": "Added the '{ add }' object", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "objects-with-methods.js" + ], + "sha1": "3006c2d8134eb46077d39614fdcb4521dbdb0b17", + "gitDir": "test/corpus/repos/javascript", + "sha2": "8c983c007eb95af974dfe614c7d1d00e09518f71" +} +,{ + "testCaseDescription": "javascript-objects-with-methods-delete-insert-test", + "expectedResult": { + "changes": { + "objects-with-methods.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 3 + ], + "name": "objects-with-methods.js", + "end": [ + 1, + 11 + ] + }, + { + "start": [ + 1, + 3 + ], + "name": "objects-with-methods.js", + "end": [ + 1, + 6 + ] + } + ] + }, + "summary": "Replaced the 'subtract' identifier with the 'add' identifier in the add method", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "objects-with-methods.js" + ], + "sha1": "8c983c007eb95af974dfe614c7d1d00e09518f71", + "gitDir": "test/corpus/repos/javascript", + "sha2": "55dcede10e26e4cf3b859b592a42217948b92144" +} +,{ + "testCaseDescription": "javascript-objects-with-methods-replacement-test", + "expectedResult": { + "changes": { + "objects-with-methods.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 3 + ], + "name": "objects-with-methods.js", + "end": [ + 1, + 6 + ] + }, + { + "start": [ + 1, + 3 + ], + "name": "objects-with-methods.js", + "end": [ + 1, + 11 + ] + } + ] + }, + "summary": "Replaced the 'add' identifier with the 'subtract' identifier in the subtract method", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "objects-with-methods.js" + ], + "sha1": "55dcede10e26e4cf3b859b592a42217948b92144", + "gitDir": "test/corpus/repos/javascript", + "sha2": "e2d692987dd8c6a20ac236a754dff49468cc37ef" +} +,{ + "testCaseDescription": "javascript-objects-with-methods-delete-replacement-test", + "expectedResult": { + "changes": { + "objects-with-methods.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "objects-with-methods.js", + "end": [ + 1, + 37 + ] + } + }, + "summary": "Deleted the '{ subtract }' object", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 1 + ], + "name": "objects-with-methods.js", + "end": [ + 2, + 32 + ] + } + }, + "summary": "Deleted the '{ add }' object", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "objects-with-methods.js", + "end": [ + 2, + 37 + ] + } + }, + "summary": "Added the '{ subtract }' object", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "objects-with-methods.js" + ], + "sha1": "e2d692987dd8c6a20ac236a754dff49468cc37ef", + "gitDir": "test/corpus/repos/javascript", + "sha2": "96aea9adf4dd98dad9f18a880cc77865485780b7" +} +,{ + "testCaseDescription": "javascript-objects-with-methods-delete-test", + "expectedResult": { + "changes": { + "objects-with-methods.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "objects-with-methods.js", + "end": [ + 1, + 32 + ] + } + }, + "summary": "Deleted the '{ add }' object", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "objects-with-methods.js" + ], + "sha1": "96aea9adf4dd98dad9f18a880cc77865485780b7", + "gitDir": "test/corpus/repos/javascript", + "sha2": "4f77fa590f5ec5abbe9af2cdf0e933c1f7930dbb" +} +,{ + "testCaseDescription": "javascript-objects-with-methods-delete-rest-test", + "expectedResult": { + "changes": { + "objects-with-methods.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "objects-with-methods.js", + "end": [ + 1, + 37 + ] + } + }, + "summary": "Deleted the '{ subtract }' object", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "objects-with-methods.js" + ], + "sha1": "4f77fa590f5ec5abbe9af2cdf0e933c1f7930dbb", + "gitDir": "test/corpus/repos/javascript", + "sha2": "b2c18e39f6754f6fbc0ce238ea24ee7386d7b34f" +}] diff --git a/test/corpus/diff-summaries/javascript/object.json b/test/corpus/diff-summaries/javascript/object.json new file mode 100644 index 000000000..294c78ddd --- /dev/null +++ b/test/corpus/diff-summaries/javascript/object.json @@ -0,0 +1,316 @@ +[{ + "testCaseDescription": "javascript-object-insert-test", + "expectedResult": { + "changes": { + "object.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "object.js", + "end": [ + 1, + 21 + ] + } + }, + "summary": "Added the '{ \"key1\": … }' object", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "object.js" + ], + "sha1": "05cde689481d4a3150edf8d68c07b711548b1c42", + "gitDir": "test/corpus/repos/javascript", + "sha2": "a82d05e8e33ae0b96a558c5e83a4c2df6de327cc" +} +,{ + "testCaseDescription": "javascript-object-replacement-insert-test", + "expectedResult": { + "changes": { + "object.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "object.js", + "end": [ + 1, + 54 + ] + } + }, + "summary": "Added the '{ \"key1\": …, \"key2\": …, \"key3\": … }' object", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "object.js", + "end": [ + 2, + 21 + ] + } + }, + "summary": "Added the '{ \"key1\": … }' object", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "object.js" + ], + "sha1": "a82d05e8e33ae0b96a558c5e83a4c2df6de327cc", + "gitDir": "test/corpus/repos/javascript", + "sha2": "6da3ab8b36cd94063af7d79dac0d1fc3681f70cd" +} +,{ + "testCaseDescription": "javascript-object-delete-insert-test", + "expectedResult": { + "changes": { + "object.js": [ + { + "span": { + "this": { + "start": [ + 1, + 21 + ], + "name": "object.js", + "end": [ + 1, + 37 + ] + } + }, + "summary": "Deleted the '\"key2\": …' pair", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 1, + 39 + ], + "name": "object.js", + "end": [ + 1, + 52 + ] + } + }, + "summary": "Deleted the '\"key3\": …' pair", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "object.js" + ], + "sha1": "6da3ab8b36cd94063af7d79dac0d1fc3681f70cd", + "gitDir": "test/corpus/repos/javascript", + "sha2": "1324b314637c3121330a2eb556e01c812056edab" +} +,{ + "testCaseDescription": "javascript-object-replacement-test", + "expectedResult": { + "changes": { + "object.js": [ + { + "span": { + "that": { + "start": [ + 1, + 21 + ], + "name": "object.js", + "end": [ + 1, + 37 + ] + } + }, + "summary": "Added the '\"key2\": …' pair", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 1, + 39 + ], + "name": "object.js", + "end": [ + 1, + 52 + ] + } + }, + "summary": "Added the '\"key3\": …' pair", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "object.js" + ], + "sha1": "1324b314637c3121330a2eb556e01c812056edab", + "gitDir": "test/corpus/repos/javascript", + "sha2": "ac121256df1e9fe9f2d385aa0410250763c35798" +} +,{ + "testCaseDescription": "javascript-object-delete-replacement-test", + "expectedResult": { + "changes": { + "object.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "object.js", + "end": [ + 1, + 54 + ] + } + }, + "summary": "Deleted the '{ \"key1\": …, \"key2\": …, \"key3\": … }' object", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 1 + ], + "name": "object.js", + "end": [ + 2, + 21 + ] + } + }, + "summary": "Deleted the '{ \"key1\": … }' object", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "object.js", + "end": [ + 2, + 54 + ] + } + }, + "summary": "Added the '{ \"key1\": …, \"key2\": …, \"key3\": … }' object", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "object.js" + ], + "sha1": "ac121256df1e9fe9f2d385aa0410250763c35798", + "gitDir": "test/corpus/repos/javascript", + "sha2": "22387f65f861db2c90f8e89e3035c436f9013523" +} +,{ + "testCaseDescription": "javascript-object-delete-test", + "expectedResult": { + "changes": { + "object.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "object.js", + "end": [ + 1, + 21 + ] + } + }, + "summary": "Deleted the '{ \"key1\": … }' object", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "object.js" + ], + "sha1": "22387f65f861db2c90f8e89e3035c436f9013523", + "gitDir": "test/corpus/repos/javascript", + "sha2": "b602e503004cc504fc1368fe867cbdc673940e91" +} +,{ + "testCaseDescription": "javascript-object-delete-rest-test", + "expectedResult": { + "changes": { + "object.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "object.js", + "end": [ + 1, + 54 + ] + } + }, + "summary": "Deleted the '{ \"key1\": …, \"key2\": …, \"key3\": … }' object", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "object.js" + ], + "sha1": "b602e503004cc504fc1368fe867cbdc673940e91", + "gitDir": "test/corpus/repos/javascript", + "sha2": "a0404e9e7b61466d953a033ff444c10691cea549" +}] diff --git a/test/corpus/diff-summaries/javascript/regex.json b/test/corpus/diff-summaries/javascript/regex.json new file mode 100644 index 000000000..f2a1c919e --- /dev/null +++ b/test/corpus/diff-summaries/javascript/regex.json @@ -0,0 +1,308 @@ +[{ + "testCaseDescription": "javascript-regex-insert-test", + "expectedResult": { + "changes": { + "regex.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "regex.js", + "end": [ + 1, + 7 + ] + } + }, + "summary": "Added the '/one/g' regex", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "regex.js" + ], + "sha1": "0578f24cf85fce35bd787e60e1b210b79f462858", + "gitDir": "test/corpus/repos/javascript", + "sha2": "f58477ae790a5642d28917f80ce0eef50d3942f8" +} +,{ + "testCaseDescription": "javascript-regex-replacement-insert-test", + "expectedResult": { + "changes": { + "regex.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "regex.js", + "end": [ + 1, + 15 + ] + } + }, + "summary": "Added the '/on[^/]afe/gim' regex", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "regex.js", + "end": [ + 2, + 7 + ] + } + }, + "summary": "Added the '/one/g' regex", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "regex.js" + ], + "sha1": "f58477ae790a5642d28917f80ce0eef50d3942f8", + "gitDir": "test/corpus/repos/javascript", + "sha2": "2a69523d4cbd85210fb91e34d2e3d780edadb84a" +} +,{ + "testCaseDescription": "javascript-regex-delete-insert-test", + "expectedResult": { + "changes": { + "regex.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 1 + ], + "name": "regex.js", + "end": [ + 1, + 15 + ] + }, + { + "start": [ + 1, + 1 + ], + "name": "regex.js", + "end": [ + 1, + 7 + ] + } + ] + }, + "summary": "Replaced the '/on[^/]afe/gim' regex with the '/one/g' regex", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "regex.js" + ], + "sha1": "2a69523d4cbd85210fb91e34d2e3d780edadb84a", + "gitDir": "test/corpus/repos/javascript", + "sha2": "0db3f4dd27fec529d440a8e90b5f163017d6d1e8" +} +,{ + "testCaseDescription": "javascript-regex-replacement-test", + "expectedResult": { + "changes": { + "regex.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 1 + ], + "name": "regex.js", + "end": [ + 1, + 7 + ] + }, + { + "start": [ + 1, + 1 + ], + "name": "regex.js", + "end": [ + 1, + 15 + ] + } + ] + }, + "summary": "Replaced the '/one/g' regex with the '/on[^/]afe/gim' regex", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "regex.js" + ], + "sha1": "0db3f4dd27fec529d440a8e90b5f163017d6d1e8", + "gitDir": "test/corpus/repos/javascript", + "sha2": "dfb43e551c9e2376cf3b7de60e4ab10aa24a1cd1" +} +,{ + "testCaseDescription": "javascript-regex-delete-replacement-test", + "expectedResult": { + "changes": { + "regex.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "regex.js", + "end": [ + 1, + 15 + ] + } + }, + "summary": "Deleted the '/on[^/]afe/gim' regex", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 1 + ], + "name": "regex.js", + "end": [ + 2, + 7 + ] + } + }, + "summary": "Deleted the '/one/g' regex", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "regex.js", + "end": [ + 2, + 15 + ] + } + }, + "summary": "Added the '/on[^/]afe/gim' regex", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "regex.js" + ], + "sha1": "dfb43e551c9e2376cf3b7de60e4ab10aa24a1cd1", + "gitDir": "test/corpus/repos/javascript", + "sha2": "a6a36758433fd19118cd451bc078fff428925b0f" +} +,{ + "testCaseDescription": "javascript-regex-delete-test", + "expectedResult": { + "changes": { + "regex.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "regex.js", + "end": [ + 1, + 7 + ] + } + }, + "summary": "Deleted the '/one/g' regex", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "regex.js" + ], + "sha1": "a6a36758433fd19118cd451bc078fff428925b0f", + "gitDir": "test/corpus/repos/javascript", + "sha2": "098252dc18d9aad40432ffc927069d1a61e76ce9" +} +,{ + "testCaseDescription": "javascript-regex-delete-rest-test", + "expectedResult": { + "changes": { + "regex.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "regex.js", + "end": [ + 1, + 15 + ] + } + }, + "summary": "Deleted the '/on[^/]afe/gim' regex", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "regex.js" + ], + "sha1": "098252dc18d9aad40432ffc927069d1a61e76ce9", + "gitDir": "test/corpus/repos/javascript", + "sha2": "1fbd44cbdd925bb727f5b07af974a37db31b3ea0" +}] diff --git a/test/corpus/diff-summaries/javascript/relational-operator.json b/test/corpus/diff-summaries/javascript/relational-operator.json new file mode 100644 index 000000000..73443a696 --- /dev/null +++ b/test/corpus/diff-summaries/javascript/relational-operator.json @@ -0,0 +1,208 @@ +[{ + "testCaseDescription": "javascript-relational-operator-insert-test", + "expectedResult": { + "changes": { + "relational-operator.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "relational-operator.js", + "end": [ + 1, + 6 + ] + } + }, + "summary": "Added the 'x < y' relational operator", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "relational-operator.js" + ], + "sha1": "4a348bc66ccc50e501fe3e49df1cd797d99ca405", + "gitDir": "test/corpus/repos/javascript", + "sha2": "ddbb70b6d30615c62f926c6e5f3b9868d8102c2b" +} +,{ + "testCaseDescription": "javascript-relational-operator-replacement-insert-test", + "expectedResult": { + "changes": { + "relational-operator.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "relational-operator.js", + "end": [ + 1, + 7 + ] + } + }, + "summary": "Added the 'x <= y' relational operator", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "relational-operator.js", + "end": [ + 2, + 6 + ] + } + }, + "summary": "Added the 'x < y' relational operator", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "relational-operator.js" + ], + "sha1": "ddbb70b6d30615c62f926c6e5f3b9868d8102c2b", + "gitDir": "test/corpus/repos/javascript", + "sha2": "e3b836e0a0b0ece117db55b8a9e4f5042fbe994a" +} +,{ + "testCaseDescription": "javascript-relational-operator-delete-insert-test", + "expectedResult": { + "changes": {}, + "errors": {} + }, + "filePaths": [ + "relational-operator.js" + ], + "sha1": "e3b836e0a0b0ece117db55b8a9e4f5042fbe994a", + "gitDir": "test/corpus/repos/javascript", + "sha2": "cecfdf6d66df9ae0c0002d04925f509d2cf27fd7" +} +,{ + "testCaseDescription": "javascript-relational-operator-replacement-test", + "expectedResult": { + "changes": {}, + "errors": {} + }, + "filePaths": [ + "relational-operator.js" + ], + "sha1": "cecfdf6d66df9ae0c0002d04925f509d2cf27fd7", + "gitDir": "test/corpus/repos/javascript", + "sha2": "9ac444b7e34c82e6280aac2751be6e1b2f7aa2e3" +} +,{ + "testCaseDescription": "javascript-relational-operator-delete-replacement-test", + "expectedResult": { + "changes": { + "relational-operator.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "relational-operator.js", + "end": [ + 1, + 7 + ] + } + }, + "summary": "Deleted the 'x <= y' relational operator", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "relational-operator.js" + ], + "sha1": "9ac444b7e34c82e6280aac2751be6e1b2f7aa2e3", + "gitDir": "test/corpus/repos/javascript", + "sha2": "9eea04a227ce9e4647d462615e7d72109ceb2bd1" +} +,{ + "testCaseDescription": "javascript-relational-operator-delete-test", + "expectedResult": { + "changes": { + "relational-operator.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "relational-operator.js", + "end": [ + 1, + 6 + ] + } + }, + "summary": "Deleted the 'x < y' relational operator", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "relational-operator.js" + ], + "sha1": "9eea04a227ce9e4647d462615e7d72109ceb2bd1", + "gitDir": "test/corpus/repos/javascript", + "sha2": "1b50dad44a6ffa8b3bde53fdd4c3dd80ba19e849" +} +,{ + "testCaseDescription": "javascript-relational-operator-delete-rest-test", + "expectedResult": { + "changes": { + "relational-operator.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "relational-operator.js", + "end": [ + 1, + 7 + ] + } + }, + "summary": "Deleted the 'x <= y' relational operator", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "relational-operator.js" + ], + "sha1": "1b50dad44a6ffa8b3bde53fdd4c3dd80ba19e849", + "gitDir": "test/corpus/repos/javascript", + "sha2": "8c6579c037e31738b4decb4405d7a17824524ca3" +}] diff --git a/test/corpus/diff-summaries/javascript/return-statement.json b/test/corpus/diff-summaries/javascript/return-statement.json new file mode 100644 index 000000000..bd06723a4 --- /dev/null +++ b/test/corpus/diff-summaries/javascript/return-statement.json @@ -0,0 +1,282 @@ +[{ + "testCaseDescription": "javascript-return-statement-insert-test", + "expectedResult": { + "changes": { + "return-statement.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "return-statement.js", + "end": [ + 1, + 10 + ] + } + }, + "summary": "Added the '5' return statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "return-statement.js" + ], + "sha1": "11ce49dc14d6c3b4c0baef54a2456d4bc667b992", + "gitDir": "test/corpus/repos/javascript", + "sha2": "c780ce189b53bd43241c7c278c5a7749dcc14d81" +} +,{ + "testCaseDescription": "javascript-return-statement-replacement-insert-test", + "expectedResult": { + "changes": { + "return-statement.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "return-statement.js", + "end": [ + 1, + 8 + ] + } + }, + "summary": "Added the 'empty' return statement", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "return-statement.js", + "end": [ + 2, + 10 + ] + } + }, + "summary": "Added the '5' return statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "return-statement.js" + ], + "sha1": "c780ce189b53bd43241c7c278c5a7749dcc14d81", + "gitDir": "test/corpus/repos/javascript", + "sha2": "219a0207a0a6f7711dbc837e9cfb87a610f9df07" +} +,{ + "testCaseDescription": "javascript-return-statement-delete-insert-test", + "expectedResult": { + "changes": { + "return-statement.js": [ + { + "span": { + "that": { + "start": [ + 1, + 8 + ], + "name": "return-statement.js", + "end": [ + 1, + 9 + ] + } + }, + "summary": "Added '5'", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "return-statement.js" + ], + "sha1": "219a0207a0a6f7711dbc837e9cfb87a610f9df07", + "gitDir": "test/corpus/repos/javascript", + "sha2": "f48d1d569a04768182d8fd9d92854d2fbd106d16" +} +,{ + "testCaseDescription": "javascript-return-statement-replacement-test", + "expectedResult": { + "changes": { + "return-statement.js": [ + { + "span": { + "this": { + "start": [ + 1, + 8 + ], + "name": "return-statement.js", + "end": [ + 1, + 9 + ] + } + }, + "summary": "Deleted '5'", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "return-statement.js" + ], + "sha1": "f48d1d569a04768182d8fd9d92854d2fbd106d16", + "gitDir": "test/corpus/repos/javascript", + "sha2": "8955ee5588fdf2e27ac4ba5a20fcf4f2c3f812ed" +} +,{ + "testCaseDescription": "javascript-return-statement-delete-replacement-test", + "expectedResult": { + "changes": { + "return-statement.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "return-statement.js", + "end": [ + 1, + 8 + ] + } + }, + "summary": "Deleted the 'empty' return statement", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 1 + ], + "name": "return-statement.js", + "end": [ + 2, + 10 + ] + } + }, + "summary": "Deleted the '5' return statement", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "return-statement.js", + "end": [ + 2, + 8 + ] + } + }, + "summary": "Added the 'empty' return statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "return-statement.js" + ], + "sha1": "8955ee5588fdf2e27ac4ba5a20fcf4f2c3f812ed", + "gitDir": "test/corpus/repos/javascript", + "sha2": "8b92b202fe3a41f9f5ad570e273e5cca32320547" +} +,{ + "testCaseDescription": "javascript-return-statement-delete-test", + "expectedResult": { + "changes": { + "return-statement.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "return-statement.js", + "end": [ + 1, + 10 + ] + } + }, + "summary": "Deleted the '5' return statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "return-statement.js" + ], + "sha1": "8b92b202fe3a41f9f5ad570e273e5cca32320547", + "gitDir": "test/corpus/repos/javascript", + "sha2": "644db02de4b5f1d4d800d643c2638d2a126e235c" +} +,{ + "testCaseDescription": "javascript-return-statement-delete-rest-test", + "expectedResult": { + "changes": { + "return-statement.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "return-statement.js", + "end": [ + 1, + 8 + ] + } + }, + "summary": "Deleted the 'empty' return statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "return-statement.js" + ], + "sha1": "644db02de4b5f1d4d800d643c2638d2a126e235c", + "gitDir": "test/corpus/repos/javascript", + "sha2": "9f1361ad761d81ff9d3b968ebeefa0f9640ae0ca" +}] diff --git a/test/corpus/diff-summaries/javascript/string.json b/test/corpus/diff-summaries/javascript/string.json new file mode 100644 index 000000000..f66a0804b --- /dev/null +++ b/test/corpus/diff-summaries/javascript/string.json @@ -0,0 +1,308 @@ +[{ + "testCaseDescription": "javascript-string-insert-test", + "expectedResult": { + "changes": { + "string.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "string.js", + "end": [ + 1, + 32 + ] + } + }, + "summary": "Added the 'A string with \"double\" quotes' string", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "string.js" + ], + "sha1": "b2c18e39f6754f6fbc0ce238ea24ee7386d7b34f", + "gitDir": "test/corpus/repos/javascript", + "sha2": "0f81035000f8efd0e62f121e0a643cc8354b9178" +} +,{ + "testCaseDescription": "javascript-string-replacement-insert-test", + "expectedResult": { + "changes": { + "string.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "string.js", + "end": [ + 1, + 42 + ] + } + }, + "summary": "Added the 'A different string with \"double\" quotes' string", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "string.js", + "end": [ + 2, + 32 + ] + } + }, + "summary": "Added the 'A string with \"double\" quotes' string", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "string.js" + ], + "sha1": "0f81035000f8efd0e62f121e0a643cc8354b9178", + "gitDir": "test/corpus/repos/javascript", + "sha2": "35dd5365f89a59f05c68a1edb5284e33847c688e" +} +,{ + "testCaseDescription": "javascript-string-delete-insert-test", + "expectedResult": { + "changes": { + "string.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 1 + ], + "name": "string.js", + "end": [ + 1, + 42 + ] + }, + { + "start": [ + 1, + 1 + ], + "name": "string.js", + "end": [ + 1, + 32 + ] + } + ] + }, + "summary": "Replaced the 'A different string with \"double\" quotes' string with the 'A string with \"double\" quotes' string", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "string.js" + ], + "sha1": "35dd5365f89a59f05c68a1edb5284e33847c688e", + "gitDir": "test/corpus/repos/javascript", + "sha2": "1234962d618b026bc92ab9ab79641e9ec21b0cac" +} +,{ + "testCaseDescription": "javascript-string-replacement-test", + "expectedResult": { + "changes": { + "string.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 1 + ], + "name": "string.js", + "end": [ + 1, + 32 + ] + }, + { + "start": [ + 1, + 1 + ], + "name": "string.js", + "end": [ + 1, + 42 + ] + } + ] + }, + "summary": "Replaced the 'A string with \"double\" quotes' string with the 'A different string with \"double\" quotes' string", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "string.js" + ], + "sha1": "1234962d618b026bc92ab9ab79641e9ec21b0cac", + "gitDir": "test/corpus/repos/javascript", + "sha2": "25ff0717d0d1ec49b053a6d07e888d0e78585c35" +} +,{ + "testCaseDescription": "javascript-string-delete-replacement-test", + "expectedResult": { + "changes": { + "string.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "string.js", + "end": [ + 1, + 42 + ] + } + }, + "summary": "Deleted the 'A different string with \"double\" quotes' string", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 1 + ], + "name": "string.js", + "end": [ + 2, + 32 + ] + } + }, + "summary": "Deleted the 'A string with \"double\" quotes' string", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "string.js", + "end": [ + 2, + 42 + ] + } + }, + "summary": "Added the 'A different string with \"double\" quotes' string", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "string.js" + ], + "sha1": "25ff0717d0d1ec49b053a6d07e888d0e78585c35", + "gitDir": "test/corpus/repos/javascript", + "sha2": "78d3c4d8e5f05bd6421f0eeeb952dc16d7855462" +} +,{ + "testCaseDescription": "javascript-string-delete-test", + "expectedResult": { + "changes": { + "string.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "string.js", + "end": [ + 1, + 32 + ] + } + }, + "summary": "Deleted the 'A string with \"double\" quotes' string", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "string.js" + ], + "sha1": "78d3c4d8e5f05bd6421f0eeeb952dc16d7855462", + "gitDir": "test/corpus/repos/javascript", + "sha2": "c2fee245e107483bd5c60ab7b0de718e822fd93a" +} +,{ + "testCaseDescription": "javascript-string-delete-rest-test", + "expectedResult": { + "changes": { + "string.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "string.js", + "end": [ + 1, + 42 + ] + } + }, + "summary": "Deleted the 'A different string with \"double\" quotes' string", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "string.js" + ], + "sha1": "c2fee245e107483bd5c60ab7b0de718e822fd93a", + "gitDir": "test/corpus/repos/javascript", + "sha2": "20b94162d6be612a1c0111cb75ee0f3beadcab6e" +}] diff --git a/test/corpus/diff-summaries/javascript/subscript-access-assignment.json b/test/corpus/diff-summaries/javascript/subscript-access-assignment.json new file mode 100644 index 000000000..1aaf98f29 --- /dev/null +++ b/test/corpus/diff-summaries/javascript/subscript-access-assignment.json @@ -0,0 +1,308 @@ +[{ + "testCaseDescription": "javascript-subscript-access-assignment-insert-test", + "expectedResult": { + "changes": { + "subscript-access-assignment.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "subscript-access-assignment.js", + "end": [ + 1, + 11 + ] + } + }, + "summary": "Added the 'y[\"x\"]' assignment", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "subscript-access-assignment.js" + ], + "sha1": "9b3e79687880bf10eac28404f1b0de7e74e0ba44", + "gitDir": "test/corpus/repos/javascript", + "sha2": "406fa823725f46c37168a5062f0fafdee1e5efff" +} +,{ + "testCaseDescription": "javascript-subscript-access-assignment-replacement-insert-test", + "expectedResult": { + "changes": { + "subscript-access-assignment.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "subscript-access-assignment.js", + "end": [ + 1, + 11 + ] + } + }, + "summary": "Added the 'y[\"x\"]' assignment", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "subscript-access-assignment.js", + "end": [ + 2, + 11 + ] + } + }, + "summary": "Added the 'y[\"x\"]' assignment", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "subscript-access-assignment.js" + ], + "sha1": "406fa823725f46c37168a5062f0fafdee1e5efff", + "gitDir": "test/corpus/repos/javascript", + "sha2": "12579d2ea4d43255f99a99bab55b6d84f4c545e8" +} +,{ + "testCaseDescription": "javascript-subscript-access-assignment-delete-insert-test", + "expectedResult": { + "changes": { + "subscript-access-assignment.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 10 + ], + "name": "subscript-access-assignment.js", + "end": [ + 1, + 11 + ] + }, + { + "start": [ + 1, + 10 + ], + "name": "subscript-access-assignment.js", + "end": [ + 1, + 11 + ] + } + ] + }, + "summary": "Replaced '1' with '0' in an assignment to y[\"x\"]", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "subscript-access-assignment.js" + ], + "sha1": "12579d2ea4d43255f99a99bab55b6d84f4c545e8", + "gitDir": "test/corpus/repos/javascript", + "sha2": "b695f35574816f1726df991f9e8a5129b6c00dbd" +} +,{ + "testCaseDescription": "javascript-subscript-access-assignment-replacement-test", + "expectedResult": { + "changes": { + "subscript-access-assignment.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 10 + ], + "name": "subscript-access-assignment.js", + "end": [ + 1, + 11 + ] + }, + { + "start": [ + 1, + 10 + ], + "name": "subscript-access-assignment.js", + "end": [ + 1, + 11 + ] + } + ] + }, + "summary": "Replaced '0' with '1' in an assignment to y[\"x\"]", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "subscript-access-assignment.js" + ], + "sha1": "b695f35574816f1726df991f9e8a5129b6c00dbd", + "gitDir": "test/corpus/repos/javascript", + "sha2": "2f092bfe85d05028172fe8c07380f7ee1c37aa3e" +} +,{ + "testCaseDescription": "javascript-subscript-access-assignment-delete-replacement-test", + "expectedResult": { + "changes": { + "subscript-access-assignment.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "subscript-access-assignment.js", + "end": [ + 1, + 11 + ] + } + }, + "summary": "Deleted the 'y[\"x\"]' assignment", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 1 + ], + "name": "subscript-access-assignment.js", + "end": [ + 2, + 11 + ] + } + }, + "summary": "Deleted the 'y[\"x\"]' assignment", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "subscript-access-assignment.js", + "end": [ + 2, + 11 + ] + } + }, + "summary": "Added the 'y[\"x\"]' assignment", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "subscript-access-assignment.js" + ], + "sha1": "2f092bfe85d05028172fe8c07380f7ee1c37aa3e", + "gitDir": "test/corpus/repos/javascript", + "sha2": "0d6c920c95f5cbbd159719a805758233c971cae8" +} +,{ + "testCaseDescription": "javascript-subscript-access-assignment-delete-test", + "expectedResult": { + "changes": { + "subscript-access-assignment.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "subscript-access-assignment.js", + "end": [ + 1, + 11 + ] + } + }, + "summary": "Deleted the 'y[\"x\"]' assignment", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "subscript-access-assignment.js" + ], + "sha1": "0d6c920c95f5cbbd159719a805758233c971cae8", + "gitDir": "test/corpus/repos/javascript", + "sha2": "015fb2b13539b87607f327118bc59c932adb151f" +} +,{ + "testCaseDescription": "javascript-subscript-access-assignment-delete-rest-test", + "expectedResult": { + "changes": { + "subscript-access-assignment.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "subscript-access-assignment.js", + "end": [ + 1, + 11 + ] + } + }, + "summary": "Deleted the 'y[\"x\"]' assignment", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "subscript-access-assignment.js" + ], + "sha1": "015fb2b13539b87607f327118bc59c932adb151f", + "gitDir": "test/corpus/repos/javascript", + "sha2": "25e371a5c0ef7434f562af7ca9a9bfab5a157932" +}] diff --git a/test/corpus/diff-summaries/javascript/subscript-access-string.json b/test/corpus/diff-summaries/javascript/subscript-access-string.json new file mode 100644 index 000000000..4facb19bf --- /dev/null +++ b/test/corpus/diff-summaries/javascript/subscript-access-string.json @@ -0,0 +1,308 @@ +[{ + "testCaseDescription": "javascript-subscript-access-string-insert-test", + "expectedResult": { + "changes": { + "subscript-access-string.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "subscript-access-string.js", + "end": [ + 1, + 17 + ] + } + }, + "summary": "Added the 'x[\"some-string\"]' subscript access", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "subscript-access-string.js" + ], + "sha1": "cbebbe0cb3d24a7adb492b88b6b5769c9b895654", + "gitDir": "test/corpus/repos/javascript", + "sha2": "b3cdd00f14a2880dee975305faf0a8268c700ca4" +} +,{ + "testCaseDescription": "javascript-subscript-access-string-replacement-insert-test", + "expectedResult": { + "changes": { + "subscript-access-string.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "subscript-access-string.js", + "end": [ + 1, + 23 + ] + } + }, + "summary": "Added the 'x[\"some-other-string\"]' subscript access", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "subscript-access-string.js", + "end": [ + 2, + 17 + ] + } + }, + "summary": "Added the 'x[\"some-string\"]' subscript access", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "subscript-access-string.js" + ], + "sha1": "b3cdd00f14a2880dee975305faf0a8268c700ca4", + "gitDir": "test/corpus/repos/javascript", + "sha2": "874fe50a89cdc77032efc2fb67e29ed8c3fbc66c" +} +,{ + "testCaseDescription": "javascript-subscript-access-string-delete-insert-test", + "expectedResult": { + "changes": { + "subscript-access-string.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 3 + ], + "name": "subscript-access-string.js", + "end": [ + 1, + 22 + ] + }, + { + "start": [ + 1, + 3 + ], + "name": "subscript-access-string.js", + "end": [ + 1, + 16 + ] + } + ] + }, + "summary": "Replaced the \"some-other-string\" string with the \"some-string\" string in the x[\"some-string\"] subscript access", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "subscript-access-string.js" + ], + "sha1": "874fe50a89cdc77032efc2fb67e29ed8c3fbc66c", + "gitDir": "test/corpus/repos/javascript", + "sha2": "86756c297918a1e4812fb77db3970d43979df6cd" +} +,{ + "testCaseDescription": "javascript-subscript-access-string-replacement-test", + "expectedResult": { + "changes": { + "subscript-access-string.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 3 + ], + "name": "subscript-access-string.js", + "end": [ + 1, + 16 + ] + }, + { + "start": [ + 1, + 3 + ], + "name": "subscript-access-string.js", + "end": [ + 1, + 22 + ] + } + ] + }, + "summary": "Replaced the \"some-string\" string with the \"some-other-string\" string in the x[\"some-other-string\"] subscript access", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "subscript-access-string.js" + ], + "sha1": "86756c297918a1e4812fb77db3970d43979df6cd", + "gitDir": "test/corpus/repos/javascript", + "sha2": "a536d6f573c0c3763b9dc6f4795362d33515ba6f" +} +,{ + "testCaseDescription": "javascript-subscript-access-string-delete-replacement-test", + "expectedResult": { + "changes": { + "subscript-access-string.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "subscript-access-string.js", + "end": [ + 1, + 23 + ] + } + }, + "summary": "Deleted the 'x[\"some-other-string\"]' subscript access", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 1 + ], + "name": "subscript-access-string.js", + "end": [ + 2, + 17 + ] + } + }, + "summary": "Deleted the 'x[\"some-string\"]' subscript access", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "subscript-access-string.js", + "end": [ + 2, + 23 + ] + } + }, + "summary": "Added the 'x[\"some-other-string\"]' subscript access", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "subscript-access-string.js" + ], + "sha1": "a536d6f573c0c3763b9dc6f4795362d33515ba6f", + "gitDir": "test/corpus/repos/javascript", + "sha2": "e9eec0492107b1e1a88b908a99081ed82cd0ac71" +} +,{ + "testCaseDescription": "javascript-subscript-access-string-delete-test", + "expectedResult": { + "changes": { + "subscript-access-string.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "subscript-access-string.js", + "end": [ + 1, + 17 + ] + } + }, + "summary": "Deleted the 'x[\"some-string\"]' subscript access", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "subscript-access-string.js" + ], + "sha1": "e9eec0492107b1e1a88b908a99081ed82cd0ac71", + "gitDir": "test/corpus/repos/javascript", + "sha2": "bd4c80248676d64aea1381b767de1d9db079caa1" +} +,{ + "testCaseDescription": "javascript-subscript-access-string-delete-rest-test", + "expectedResult": { + "changes": { + "subscript-access-string.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "subscript-access-string.js", + "end": [ + 1, + 23 + ] + } + }, + "summary": "Deleted the 'x[\"some-other-string\"]' subscript access", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "subscript-access-string.js" + ], + "sha1": "bd4c80248676d64aea1381b767de1d9db079caa1", + "gitDir": "test/corpus/repos/javascript", + "sha2": "5172568a010252e98966d57a1c3fc1ade326f9ab" +}] diff --git a/test/corpus/diff-summaries/javascript/subscript-access-variable.json b/test/corpus/diff-summaries/javascript/subscript-access-variable.json new file mode 100644 index 000000000..ce75675d4 --- /dev/null +++ b/test/corpus/diff-summaries/javascript/subscript-access-variable.json @@ -0,0 +1,308 @@ +[{ + "testCaseDescription": "javascript-subscript-access-variable-insert-test", + "expectedResult": { + "changes": { + "subscript-access-variable.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "subscript-access-variable.js", + "end": [ + 1, + 16 + ] + } + }, + "summary": "Added the 'x[someVariable]' subscript access", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "subscript-access-variable.js" + ], + "sha1": "c11043ad084bd837ff463621da19892d2cc68719", + "gitDir": "test/corpus/repos/javascript", + "sha2": "a076ecf316a9547bedf74871f24d1722e3f3cfff" +} +,{ + "testCaseDescription": "javascript-subscript-access-variable-replacement-insert-test", + "expectedResult": { + "changes": { + "subscript-access-variable.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "subscript-access-variable.js", + "end": [ + 1, + 21 + ] + } + }, + "summary": "Added the 'x[someOtherVariable]' subscript access", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "subscript-access-variable.js", + "end": [ + 2, + 16 + ] + } + }, + "summary": "Added the 'x[someVariable]' subscript access", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "subscript-access-variable.js" + ], + "sha1": "a076ecf316a9547bedf74871f24d1722e3f3cfff", + "gitDir": "test/corpus/repos/javascript", + "sha2": "532af784b3b0f34834c09220cae84e8685973ce5" +} +,{ + "testCaseDescription": "javascript-subscript-access-variable-delete-insert-test", + "expectedResult": { + "changes": { + "subscript-access-variable.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 3 + ], + "name": "subscript-access-variable.js", + "end": [ + 1, + 20 + ] + }, + { + "start": [ + 1, + 3 + ], + "name": "subscript-access-variable.js", + "end": [ + 1, + 15 + ] + } + ] + }, + "summary": "Replaced the 'someOtherVariable' identifier with the 'someVariable' identifier in the x[someVariable] subscript access", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "subscript-access-variable.js" + ], + "sha1": "532af784b3b0f34834c09220cae84e8685973ce5", + "gitDir": "test/corpus/repos/javascript", + "sha2": "1d5d4545a5ebd95ec639b5cbd0b8ddf370f6a9bb" +} +,{ + "testCaseDescription": "javascript-subscript-access-variable-replacement-test", + "expectedResult": { + "changes": { + "subscript-access-variable.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 3 + ], + "name": "subscript-access-variable.js", + "end": [ + 1, + 15 + ] + }, + { + "start": [ + 1, + 3 + ], + "name": "subscript-access-variable.js", + "end": [ + 1, + 20 + ] + } + ] + }, + "summary": "Replaced the 'someVariable' identifier with the 'someOtherVariable' identifier in the x[someOtherVariable] subscript access", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "subscript-access-variable.js" + ], + "sha1": "1d5d4545a5ebd95ec639b5cbd0b8ddf370f6a9bb", + "gitDir": "test/corpus/repos/javascript", + "sha2": "f24b4aa4b2d05fa5f999084bc6dc9fb783410c34" +} +,{ + "testCaseDescription": "javascript-subscript-access-variable-delete-replacement-test", + "expectedResult": { + "changes": { + "subscript-access-variable.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "subscript-access-variable.js", + "end": [ + 1, + 21 + ] + } + }, + "summary": "Deleted the 'x[someOtherVariable]' subscript access", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 1 + ], + "name": "subscript-access-variable.js", + "end": [ + 2, + 16 + ] + } + }, + "summary": "Deleted the 'x[someVariable]' subscript access", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "subscript-access-variable.js", + "end": [ + 2, + 21 + ] + } + }, + "summary": "Added the 'x[someOtherVariable]' subscript access", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "subscript-access-variable.js" + ], + "sha1": "f24b4aa4b2d05fa5f999084bc6dc9fb783410c34", + "gitDir": "test/corpus/repos/javascript", + "sha2": "4226b1e07671ad870d12e6e5942b38bf608049ab" +} +,{ + "testCaseDescription": "javascript-subscript-access-variable-delete-test", + "expectedResult": { + "changes": { + "subscript-access-variable.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "subscript-access-variable.js", + "end": [ + 1, + 16 + ] + } + }, + "summary": "Deleted the 'x[someVariable]' subscript access", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "subscript-access-variable.js" + ], + "sha1": "4226b1e07671ad870d12e6e5942b38bf608049ab", + "gitDir": "test/corpus/repos/javascript", + "sha2": "e6f147e5c8d95e515d4a599a02e9601d59d95026" +} +,{ + "testCaseDescription": "javascript-subscript-access-variable-delete-rest-test", + "expectedResult": { + "changes": { + "subscript-access-variable.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "subscript-access-variable.js", + "end": [ + 1, + 21 + ] + } + }, + "summary": "Deleted the 'x[someOtherVariable]' subscript access", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "subscript-access-variable.js" + ], + "sha1": "e6f147e5c8d95e515d4a599a02e9601d59d95026", + "gitDir": "test/corpus/repos/javascript", + "sha2": "cbebbe0cb3d24a7adb492b88b6b5769c9b895654" +}] diff --git a/test/corpus/diff-summaries/javascript/switch-statement.json b/test/corpus/diff-summaries/javascript/switch-statement.json new file mode 100644 index 000000000..d223a4e32 --- /dev/null +++ b/test/corpus/diff-summaries/javascript/switch-statement.json @@ -0,0 +1,368 @@ +[{ + "testCaseDescription": "javascript-switch-statement-insert-test", + "expectedResult": { + "changes": { + "switch-statement.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "switch-statement.js", + "end": [ + 1, + 48 + ] + } + }, + "summary": "Added the '1' switch statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "switch-statement.js" + ], + "sha1": "9edcc470495aad2ae2b395a18179ec07829ad591", + "gitDir": "test/corpus/repos/javascript", + "sha2": "1acb22650fd13ec0e21402cea65bcdb4e213de86" +} +,{ + "testCaseDescription": "javascript-switch-statement-replacement-insert-test", + "expectedResult": { + "changes": { + "switch-statement.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "switch-statement.js", + "end": [ + 1, + 48 + ] + } + }, + "summary": "Added the '2' switch statement", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "switch-statement.js", + "end": [ + 2, + 48 + ] + } + }, + "summary": "Added the '1' switch statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "switch-statement.js" + ], + "sha1": "1acb22650fd13ec0e21402cea65bcdb4e213de86", + "gitDir": "test/corpus/repos/javascript", + "sha2": "97c934a7e12be096627bbdd511c6d3ac1b1bfa7e" +} +,{ + "testCaseDescription": "javascript-switch-statement-delete-insert-test", + "expectedResult": { + "changes": { + "switch-statement.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 9 + ], + "name": "switch-statement.js", + "end": [ + 1, + 10 + ] + }, + { + "start": [ + 1, + 9 + ], + "name": "switch-statement.js", + "end": [ + 1, + 10 + ] + } + ] + }, + "summary": "Replaced '2' with '1'", + "tag": "JSONSummary" + }, + { + "span": { + "these": [ + { + "start": [ + 1, + 33 + ], + "name": "switch-statement.js", + "end": [ + 1, + 34 + ] + }, + { + "start": [ + 1, + 33 + ], + "name": "switch-statement.js", + "end": [ + 1, + 34 + ] + } + ] + }, + "summary": "Replaced '2' with '1'", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "switch-statement.js" + ], + "sha1": "97c934a7e12be096627bbdd511c6d3ac1b1bfa7e", + "gitDir": "test/corpus/repos/javascript", + "sha2": "4010f253012dac96ff51ed3ce12d7e4a25962969" +} +,{ + "testCaseDescription": "javascript-switch-statement-replacement-test", + "expectedResult": { + "changes": { + "switch-statement.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 9 + ], + "name": "switch-statement.js", + "end": [ + 1, + 10 + ] + }, + { + "start": [ + 1, + 9 + ], + "name": "switch-statement.js", + "end": [ + 1, + 10 + ] + } + ] + }, + "summary": "Replaced '1' with '2'", + "tag": "JSONSummary" + }, + { + "span": { + "these": [ + { + "start": [ + 1, + 33 + ], + "name": "switch-statement.js", + "end": [ + 1, + 34 + ] + }, + { + "start": [ + 1, + 33 + ], + "name": "switch-statement.js", + "end": [ + 1, + 34 + ] + } + ] + }, + "summary": "Replaced '1' with '2'", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "switch-statement.js" + ], + "sha1": "4010f253012dac96ff51ed3ce12d7e4a25962969", + "gitDir": "test/corpus/repos/javascript", + "sha2": "c1e7946102306073d5951a4d9636782f92f31e50" +} +,{ + "testCaseDescription": "javascript-switch-statement-delete-replacement-test", + "expectedResult": { + "changes": { + "switch-statement.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "switch-statement.js", + "end": [ + 1, + 48 + ] + } + }, + "summary": "Deleted the '2' switch statement", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 1 + ], + "name": "switch-statement.js", + "end": [ + 2, + 48 + ] + } + }, + "summary": "Deleted the '1' switch statement", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "switch-statement.js", + "end": [ + 2, + 48 + ] + } + }, + "summary": "Added the '2' switch statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "switch-statement.js" + ], + "sha1": "c1e7946102306073d5951a4d9636782f92f31e50", + "gitDir": "test/corpus/repos/javascript", + "sha2": "23b62bde7c3eca7299b178544ed4684eb2b2c10e" +} +,{ + "testCaseDescription": "javascript-switch-statement-delete-test", + "expectedResult": { + "changes": { + "switch-statement.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "switch-statement.js", + "end": [ + 1, + 48 + ] + } + }, + "summary": "Deleted the '1' switch statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "switch-statement.js" + ], + "sha1": "23b62bde7c3eca7299b178544ed4684eb2b2c10e", + "gitDir": "test/corpus/repos/javascript", + "sha2": "289789d38eff4a6cb05cd1d6f108ce4b891e5cc0" +} +,{ + "testCaseDescription": "javascript-switch-statement-delete-rest-test", + "expectedResult": { + "changes": { + "switch-statement.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "switch-statement.js", + "end": [ + 1, + 48 + ] + } + }, + "summary": "Deleted the '2' switch statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "switch-statement.js" + ], + "sha1": "289789d38eff4a6cb05cd1d6f108ce4b891e5cc0", + "gitDir": "test/corpus/repos/javascript", + "sha2": "e2ffe71cd07060d1601caa470aa1936a882365aa" +}] diff --git a/test/corpus/diff-summaries/javascript/template-string.json b/test/corpus/diff-summaries/javascript/template-string.json new file mode 100644 index 000000000..9282fa911 --- /dev/null +++ b/test/corpus/diff-summaries/javascript/template-string.json @@ -0,0 +1,308 @@ +[{ + "testCaseDescription": "javascript-template-string-insert-test", + "expectedResult": { + "changes": { + "template-string.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "template-string.js", + "end": [ + 1, + 11 + ] + } + }, + "summary": "Added the '`one line`' template string", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "template-string.js" + ], + "sha1": "8626ab02829f07b2f15f25da58eb41b69afd53e3", + "gitDir": "test/corpus/repos/javascript", + "sha2": "d01fd0596a0ab6b147d7424546f7b0996adc1fba" +} +,{ + "testCaseDescription": "javascript-template-string-replacement-insert-test", + "expectedResult": { + "changes": { + "template-string.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "template-string.js", + "end": [ + 1, + 13 + ] + } + }, + "summary": "Added the '`multi line`' template string", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "template-string.js", + "end": [ + 2, + 11 + ] + } + }, + "summary": "Added the '`one line`' template string", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "template-string.js" + ], + "sha1": "d01fd0596a0ab6b147d7424546f7b0996adc1fba", + "gitDir": "test/corpus/repos/javascript", + "sha2": "6e7f81c46d45fea5206a006ceaa2d82ec8f78f61" +} +,{ + "testCaseDescription": "javascript-template-string-delete-insert-test", + "expectedResult": { + "changes": { + "template-string.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 1 + ], + "name": "template-string.js", + "end": [ + 1, + 13 + ] + }, + { + "start": [ + 1, + 1 + ], + "name": "template-string.js", + "end": [ + 1, + 11 + ] + } + ] + }, + "summary": "Replaced the '`multi line`' template string with the '`one line`' template string", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "template-string.js" + ], + "sha1": "6e7f81c46d45fea5206a006ceaa2d82ec8f78f61", + "gitDir": "test/corpus/repos/javascript", + "sha2": "edb72e08b538368a53cf59d2267434e98cc07b0b" +} +,{ + "testCaseDescription": "javascript-template-string-replacement-test", + "expectedResult": { + "changes": { + "template-string.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 1 + ], + "name": "template-string.js", + "end": [ + 1, + 11 + ] + }, + { + "start": [ + 1, + 1 + ], + "name": "template-string.js", + "end": [ + 1, + 13 + ] + } + ] + }, + "summary": "Replaced the '`one line`' template string with the '`multi line`' template string", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "template-string.js" + ], + "sha1": "edb72e08b538368a53cf59d2267434e98cc07b0b", + "gitDir": "test/corpus/repos/javascript", + "sha2": "4d026aa2de0873035dae443cf69517b3e587cb49" +} +,{ + "testCaseDescription": "javascript-template-string-delete-replacement-test", + "expectedResult": { + "changes": { + "template-string.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "template-string.js", + "end": [ + 1, + 13 + ] + } + }, + "summary": "Deleted the '`multi line`' template string", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 1 + ], + "name": "template-string.js", + "end": [ + 2, + 11 + ] + } + }, + "summary": "Deleted the '`one line`' template string", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "template-string.js", + "end": [ + 2, + 13 + ] + } + }, + "summary": "Added the '`multi line`' template string", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "template-string.js" + ], + "sha1": "4d026aa2de0873035dae443cf69517b3e587cb49", + "gitDir": "test/corpus/repos/javascript", + "sha2": "6eeca042e59e8a58d11b6e4829af1da4f297a099" +} +,{ + "testCaseDescription": "javascript-template-string-delete-test", + "expectedResult": { + "changes": { + "template-string.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "template-string.js", + "end": [ + 1, + 11 + ] + } + }, + "summary": "Deleted the '`one line`' template string", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "template-string.js" + ], + "sha1": "6eeca042e59e8a58d11b6e4829af1da4f297a099", + "gitDir": "test/corpus/repos/javascript", + "sha2": "c37aba59f9d510463c64e52a14eb1da928d668ee" +} +,{ + "testCaseDescription": "javascript-template-string-delete-rest-test", + "expectedResult": { + "changes": { + "template-string.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "template-string.js", + "end": [ + 1, + 13 + ] + } + }, + "summary": "Deleted the '`multi line`' template string", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "template-string.js" + ], + "sha1": "c37aba59f9d510463c64e52a14eb1da928d668ee", + "gitDir": "test/corpus/repos/javascript", + "sha2": "215eb7570ac9ccb686598ee7a6c1ddc9c0562224" +}] diff --git a/test/corpus/diff-summaries/javascript/ternary.json b/test/corpus/diff-summaries/javascript/ternary.json new file mode 100644 index 000000000..f26c4d027 --- /dev/null +++ b/test/corpus/diff-summaries/javascript/ternary.json @@ -0,0 +1,316 @@ +[{ + "testCaseDescription": "javascript-ternary-insert-test", + "expectedResult": { + "changes": { + "ternary.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "ternary.js", + "end": [ + 1, + 26 + ] + } + }, + "summary": "Added the 'condition' ternary expression", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "ternary.js" + ], + "sha1": "7086396295d14f41207e8fbae4d350f2672a77dd", + "gitDir": "test/corpus/repos/javascript", + "sha2": "8a1fe236a211694d9fb84e254d894597ddaa0cd6" +} +,{ + "testCaseDescription": "javascript-ternary-replacement-insert-test", + "expectedResult": { + "changes": { + "ternary.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "ternary.js", + "end": [ + 1, + 51 + ] + } + }, + "summary": "Added the 'x.y' assignment", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "ternary.js", + "end": [ + 2, + 26 + ] + } + }, + "summary": "Added the 'condition' ternary expression", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "ternary.js" + ], + "sha1": "8a1fe236a211694d9fb84e254d894597ddaa0cd6", + "gitDir": "test/corpus/repos/javascript", + "sha2": "6ac46b3a4b87fb3a90150d336ad4a8ae1f1b63f7" +} +,{ + "testCaseDescription": "javascript-ternary-delete-insert-test", + "expectedResult": { + "changes": { + "ternary.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "ternary.js", + "end": [ + 1, + 26 + ] + } + }, + "summary": "Added the 'condition' ternary expression", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "ternary.js", + "end": [ + 1, + 51 + ] + } + }, + "summary": "Deleted the 'x.y' assignment", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "ternary.js" + ], + "sha1": "6ac46b3a4b87fb3a90150d336ad4a8ae1f1b63f7", + "gitDir": "test/corpus/repos/javascript", + "sha2": "f3c918ef30afcdad6de0e05fa3886964a72b0029" +} +,{ + "testCaseDescription": "javascript-ternary-replacement-test", + "expectedResult": { + "changes": { + "ternary.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "ternary.js", + "end": [ + 1, + 51 + ] + } + }, + "summary": "Added the 'x.y' assignment", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "ternary.js", + "end": [ + 1, + 26 + ] + } + }, + "summary": "Deleted the 'condition' ternary expression", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "ternary.js" + ], + "sha1": "f3c918ef30afcdad6de0e05fa3886964a72b0029", + "gitDir": "test/corpus/repos/javascript", + "sha2": "eda16e19b40607bb335535a7c03378dfb511c030" +} +,{ + "testCaseDescription": "javascript-ternary-delete-replacement-test", + "expectedResult": { + "changes": { + "ternary.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "ternary.js", + "end": [ + 1, + 51 + ] + } + }, + "summary": "Deleted the 'x.y' assignment", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 1 + ], + "name": "ternary.js", + "end": [ + 2, + 26 + ] + } + }, + "summary": "Deleted the 'condition' ternary expression", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "ternary.js", + "end": [ + 2, + 51 + ] + } + }, + "summary": "Added the 'x.y' assignment", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "ternary.js" + ], + "sha1": "eda16e19b40607bb335535a7c03378dfb511c030", + "gitDir": "test/corpus/repos/javascript", + "sha2": "63a42f2ef52ae2fdb8545cc7153c9b833cee6860" +} +,{ + "testCaseDescription": "javascript-ternary-delete-test", + "expectedResult": { + "changes": { + "ternary.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "ternary.js", + "end": [ + 1, + 26 + ] + } + }, + "summary": "Deleted the 'condition' ternary expression", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "ternary.js" + ], + "sha1": "63a42f2ef52ae2fdb8545cc7153c9b833cee6860", + "gitDir": "test/corpus/repos/javascript", + "sha2": "4490621208793b8eefec135b9971666038456188" +} +,{ + "testCaseDescription": "javascript-ternary-delete-rest-test", + "expectedResult": { + "changes": { + "ternary.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "ternary.js", + "end": [ + 1, + 51 + ] + } + }, + "summary": "Deleted the 'x.y' assignment", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "ternary.js" + ], + "sha1": "4490621208793b8eefec135b9971666038456188", + "gitDir": "test/corpus/repos/javascript", + "sha2": "f01711cd334d609eaf2763a3694e94c771e37f3e" +}] diff --git a/test/corpus/diff-summaries/javascript/this-expression.json b/test/corpus/diff-summaries/javascript/this-expression.json new file mode 100644 index 000000000..9af9977ef --- /dev/null +++ b/test/corpus/diff-summaries/javascript/this-expression.json @@ -0,0 +1,316 @@ +[{ + "testCaseDescription": "javascript-this-expression-insert-test", + "expectedResult": { + "changes": { + "this-expression.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "this-expression.js", + "end": [ + 1, + 5 + ] + } + }, + "summary": "Added the 'this' identifier", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "this-expression.js" + ], + "sha1": "7a8a0da7d72fa0fc4f17e0877fbf7991771801e4", + "gitDir": "test/corpus/repos/javascript", + "sha2": "4e68235a410989b6668d753c43e95d7ea82a20ab" +} +,{ + "testCaseDescription": "javascript-this-expression-replacement-insert-test", + "expectedResult": { + "changes": { + "this-expression.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "this-expression.js", + "end": [ + 1, + 13 + ] + } + }, + "summary": "Added the 'this' return statement", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "this-expression.js", + "end": [ + 2, + 5 + ] + } + }, + "summary": "Added the 'this' identifier", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "this-expression.js" + ], + "sha1": "4e68235a410989b6668d753c43e95d7ea82a20ab", + "gitDir": "test/corpus/repos/javascript", + "sha2": "1eaabc425a7661277a9ac52b3e5189db025ad881" +} +,{ + "testCaseDescription": "javascript-this-expression-delete-insert-test", + "expectedResult": { + "changes": { + "this-expression.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "this-expression.js", + "end": [ + 1, + 5 + ] + } + }, + "summary": "Added the 'this' identifier", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "this-expression.js", + "end": [ + 1, + 13 + ] + } + }, + "summary": "Deleted the 'this' return statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "this-expression.js" + ], + "sha1": "1eaabc425a7661277a9ac52b3e5189db025ad881", + "gitDir": "test/corpus/repos/javascript", + "sha2": "ebdf7cb1b6e208ba778abad19c2cbf3ca29266ed" +} +,{ + "testCaseDescription": "javascript-this-expression-replacement-test", + "expectedResult": { + "changes": { + "this-expression.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "this-expression.js", + "end": [ + 1, + 13 + ] + } + }, + "summary": "Added the 'this' return statement", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "this-expression.js", + "end": [ + 1, + 5 + ] + } + }, + "summary": "Deleted the 'this' identifier", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "this-expression.js" + ], + "sha1": "ebdf7cb1b6e208ba778abad19c2cbf3ca29266ed", + "gitDir": "test/corpus/repos/javascript", + "sha2": "f7f8f21aeaebe6a982a1f3a21fcdf54bb9015b88" +} +,{ + "testCaseDescription": "javascript-this-expression-delete-replacement-test", + "expectedResult": { + "changes": { + "this-expression.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "this-expression.js", + "end": [ + 1, + 13 + ] + } + }, + "summary": "Deleted the 'this' return statement", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 1 + ], + "name": "this-expression.js", + "end": [ + 2, + 5 + ] + } + }, + "summary": "Deleted the 'this' identifier", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "this-expression.js", + "end": [ + 2, + 13 + ] + } + }, + "summary": "Added the 'this' return statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "this-expression.js" + ], + "sha1": "f7f8f21aeaebe6a982a1f3a21fcdf54bb9015b88", + "gitDir": "test/corpus/repos/javascript", + "sha2": "d93d9eecbb0719107fe145d07a5ce4acd1e38e2a" +} +,{ + "testCaseDescription": "javascript-this-expression-delete-test", + "expectedResult": { + "changes": { + "this-expression.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "this-expression.js", + "end": [ + 1, + 5 + ] + } + }, + "summary": "Deleted the 'this' identifier", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "this-expression.js" + ], + "sha1": "d93d9eecbb0719107fe145d07a5ce4acd1e38e2a", + "gitDir": "test/corpus/repos/javascript", + "sha2": "2cde04d533ec65accf0c7a86021a2f40b593135c" +} +,{ + "testCaseDescription": "javascript-this-expression-delete-rest-test", + "expectedResult": { + "changes": { + "this-expression.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "this-expression.js", + "end": [ + 1, + 13 + ] + } + }, + "summary": "Deleted the 'this' return statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "this-expression.js" + ], + "sha1": "2cde04d533ec65accf0c7a86021a2f40b593135c", + "gitDir": "test/corpus/repos/javascript", + "sha2": "e876cda8f0a6a14bd8518d84e985c6616b2f5548" +}] diff --git a/test/corpus/diff-summaries/javascript/throw-statement.json b/test/corpus/diff-summaries/javascript/throw-statement.json new file mode 100644 index 000000000..0c071fdd0 --- /dev/null +++ b/test/corpus/diff-summaries/javascript/throw-statement.json @@ -0,0 +1,308 @@ +[{ + "testCaseDescription": "javascript-throw-statement-insert-test", + "expectedResult": { + "changes": { + "throw-statement.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "throw-statement.js", + "end": [ + 1, + 26 + ] + } + }, + "summary": "Added the 'new Error(\"uh oh\")' throw statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "throw-statement.js" + ], + "sha1": "e2ffe71cd07060d1601caa470aa1936a882365aa", + "gitDir": "test/corpus/repos/javascript", + "sha2": "363abd980205793325903f7663a8aba813853c60" +} +,{ + "testCaseDescription": "javascript-throw-statement-replacement-insert-test", + "expectedResult": { + "changes": { + "throw-statement.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "throw-statement.js", + "end": [ + 1, + 29 + ] + } + }, + "summary": "Added the 'new Error(\"oooooops\")' throw statement", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "throw-statement.js", + "end": [ + 2, + 26 + ] + } + }, + "summary": "Added the 'new Error(\"uh oh\")' throw statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "throw-statement.js" + ], + "sha1": "363abd980205793325903f7663a8aba813853c60", + "gitDir": "test/corpus/repos/javascript", + "sha2": "82955fc3b94492fd9bc3781b544bffd24218c946" +} +,{ + "testCaseDescription": "javascript-throw-statement-delete-insert-test", + "expectedResult": { + "changes": { + "throw-statement.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 17 + ], + "name": "throw-statement.js", + "end": [ + 1, + 27 + ] + }, + { + "start": [ + 1, + 17 + ], + "name": "throw-statement.js", + "end": [ + 1, + 24 + ] + } + ] + }, + "summary": "Replaced the \"oooooops\" string with the \"uh oh\" string in the Error(\"uh oh\") function call", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "throw-statement.js" + ], + "sha1": "82955fc3b94492fd9bc3781b544bffd24218c946", + "gitDir": "test/corpus/repos/javascript", + "sha2": "f02d91e624715dab97abdc40d8f85c41b03059d3" +} +,{ + "testCaseDescription": "javascript-throw-statement-replacement-test", + "expectedResult": { + "changes": { + "throw-statement.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 17 + ], + "name": "throw-statement.js", + "end": [ + 1, + 24 + ] + }, + { + "start": [ + 1, + 17 + ], + "name": "throw-statement.js", + "end": [ + 1, + 27 + ] + } + ] + }, + "summary": "Replaced the \"uh oh\" string with the \"oooooops\" string in the Error(\"oooooops\") function call", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "throw-statement.js" + ], + "sha1": "f02d91e624715dab97abdc40d8f85c41b03059d3", + "gitDir": "test/corpus/repos/javascript", + "sha2": "999ce8327ac58820d2d5bbac312c0848974b628b" +} +,{ + "testCaseDescription": "javascript-throw-statement-delete-replacement-test", + "expectedResult": { + "changes": { + "throw-statement.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "throw-statement.js", + "end": [ + 1, + 29 + ] + } + }, + "summary": "Deleted the 'new Error(\"oooooops\")' throw statement", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 1 + ], + "name": "throw-statement.js", + "end": [ + 2, + 26 + ] + } + }, + "summary": "Deleted the 'new Error(\"uh oh\")' throw statement", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "throw-statement.js", + "end": [ + 2, + 29 + ] + } + }, + "summary": "Added the 'new Error(\"oooooops\")' throw statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "throw-statement.js" + ], + "sha1": "999ce8327ac58820d2d5bbac312c0848974b628b", + "gitDir": "test/corpus/repos/javascript", + "sha2": "bcb93927bbea7b965623d9fb3be8394b1b4ab89f" +} +,{ + "testCaseDescription": "javascript-throw-statement-delete-test", + "expectedResult": { + "changes": { + "throw-statement.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "throw-statement.js", + "end": [ + 1, + 26 + ] + } + }, + "summary": "Deleted the 'new Error(\"uh oh\")' throw statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "throw-statement.js" + ], + "sha1": "bcb93927bbea7b965623d9fb3be8394b1b4ab89f", + "gitDir": "test/corpus/repos/javascript", + "sha2": "71579a278eeefa1b2d0bb5c8468c399a7e195c06" +} +,{ + "testCaseDescription": "javascript-throw-statement-delete-rest-test", + "expectedResult": { + "changes": { + "throw-statement.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "throw-statement.js", + "end": [ + 1, + 29 + ] + } + }, + "summary": "Deleted the 'new Error(\"oooooops\")' throw statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "throw-statement.js" + ], + "sha1": "71579a278eeefa1b2d0bb5c8468c399a7e195c06", + "gitDir": "test/corpus/repos/javascript", + "sha2": "5044aaf60e72175bafaddfb99e8e548b34647376" +}] diff --git a/test/corpus/diff-summaries/javascript/true.json b/test/corpus/diff-summaries/javascript/true.json new file mode 100644 index 000000000..bb0c8d921 --- /dev/null +++ b/test/corpus/diff-summaries/javascript/true.json @@ -0,0 +1,316 @@ +[{ + "testCaseDescription": "javascript-true-insert-test", + "expectedResult": { + "changes": { + "true.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "true.js", + "end": [ + 1, + 5 + ] + } + }, + "summary": "Added 'true'", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "true.js" + ], + "sha1": "230a472f82fce3b0be97b48298c0b3db54007c5c", + "gitDir": "test/corpus/repos/javascript", + "sha2": "043d01b853e537966ee01a5f9d9c7290b33ce134" +} +,{ + "testCaseDescription": "javascript-true-replacement-insert-test", + "expectedResult": { + "changes": { + "true.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "true.js", + "end": [ + 1, + 13 + ] + } + }, + "summary": "Added the 'true' return statement", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "true.js", + "end": [ + 2, + 5 + ] + } + }, + "summary": "Added 'true'", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "true.js" + ], + "sha1": "043d01b853e537966ee01a5f9d9c7290b33ce134", + "gitDir": "test/corpus/repos/javascript", + "sha2": "02cef50d45506ede85c96b11f33bd059c89f5ee7" +} +,{ + "testCaseDescription": "javascript-true-delete-insert-test", + "expectedResult": { + "changes": { + "true.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "true.js", + "end": [ + 1, + 5 + ] + } + }, + "summary": "Added 'true'", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "true.js", + "end": [ + 1, + 13 + ] + } + }, + "summary": "Deleted the 'true' return statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "true.js" + ], + "sha1": "02cef50d45506ede85c96b11f33bd059c89f5ee7", + "gitDir": "test/corpus/repos/javascript", + "sha2": "b170ce196e79b7886a3e2dc39a834228cc8d6374" +} +,{ + "testCaseDescription": "javascript-true-replacement-test", + "expectedResult": { + "changes": { + "true.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "true.js", + "end": [ + 1, + 13 + ] + } + }, + "summary": "Added the 'true' return statement", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "true.js", + "end": [ + 1, + 5 + ] + } + }, + "summary": "Deleted 'true'", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "true.js" + ], + "sha1": "b170ce196e79b7886a3e2dc39a834228cc8d6374", + "gitDir": "test/corpus/repos/javascript", + "sha2": "1630f9afc6e883c6054d6c17d079b5a021d60314" +} +,{ + "testCaseDescription": "javascript-true-delete-replacement-test", + "expectedResult": { + "changes": { + "true.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "true.js", + "end": [ + 1, + 13 + ] + } + }, + "summary": "Deleted the 'true' return statement", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 1 + ], + "name": "true.js", + "end": [ + 2, + 5 + ] + } + }, + "summary": "Deleted 'true'", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "true.js", + "end": [ + 2, + 13 + ] + } + }, + "summary": "Added the 'true' return statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "true.js" + ], + "sha1": "1630f9afc6e883c6054d6c17d079b5a021d60314", + "gitDir": "test/corpus/repos/javascript", + "sha2": "53420b8c2df9618edf44659f29dbf259aa768aa4" +} +,{ + "testCaseDescription": "javascript-true-delete-test", + "expectedResult": { + "changes": { + "true.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "true.js", + "end": [ + 1, + 5 + ] + } + }, + "summary": "Deleted 'true'", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "true.js" + ], + "sha1": "53420b8c2df9618edf44659f29dbf259aa768aa4", + "gitDir": "test/corpus/repos/javascript", + "sha2": "21ba042d79f5a739f4873d860802f39b15299d6b" +} +,{ + "testCaseDescription": "javascript-true-delete-rest-test", + "expectedResult": { + "changes": { + "true.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "true.js", + "end": [ + 1, + 13 + ] + } + }, + "summary": "Deleted the 'true' return statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "true.js" + ], + "sha1": "21ba042d79f5a739f4873d860802f39b15299d6b", + "gitDir": "test/corpus/repos/javascript", + "sha2": "9c5eadaa5e35756fff0d96ba9830a7e0dbf30fd7" +}] diff --git a/test/corpus/diff-summaries/javascript/try-statement.json b/test/corpus/diff-summaries/javascript/try-statement.json new file mode 100644 index 000000000..9640a7d15 --- /dev/null +++ b/test/corpus/diff-summaries/javascript/try-statement.json @@ -0,0 +1,368 @@ +[{ + "testCaseDescription": "javascript-try-statement-insert-test", + "expectedResult": { + "changes": { + "try-statement.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "try-statement.js", + "end": [ + 1, + 39 + ] + } + }, + "summary": "Added the '{ f; }' try statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "try-statement.js" + ], + "sha1": "5044aaf60e72175bafaddfb99e8e548b34647376", + "gitDir": "test/corpus/repos/javascript", + "sha2": "934746aee66c0c2cb37cb4affbb09ff6c9c896e4" +} +,{ + "testCaseDescription": "javascript-try-statement-replacement-insert-test", + "expectedResult": { + "changes": { + "try-statement.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "try-statement.js", + "end": [ + 1, + 39 + ] + } + }, + "summary": "Added the '{ f; }' try statement", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "try-statement.js", + "end": [ + 2, + 39 + ] + } + }, + "summary": "Added the '{ f; }' try statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "try-statement.js" + ], + "sha1": "934746aee66c0c2cb37cb4affbb09ff6c9c896e4", + "gitDir": "test/corpus/repos/javascript", + "sha2": "3ca670bfa75c6a1708e8cbefcf5709baf85165b9" +} +,{ + "testCaseDescription": "javascript-try-statement-delete-insert-test", + "expectedResult": { + "changes": { + "try-statement.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 20 + ], + "name": "try-statement.js", + "end": [ + 1, + 21 + ] + }, + { + "start": [ + 1, + 20 + ], + "name": "try-statement.js", + "end": [ + 1, + 21 + ] + } + ] + }, + "summary": "Replaced the 'h' identifier with the 'g' identifier", + "tag": "JSONSummary" + }, + { + "span": { + "these": [ + { + "start": [ + 1, + 35 + ], + "name": "try-statement.js", + "end": [ + 1, + 36 + ] + }, + { + "start": [ + 1, + 35 + ], + "name": "try-statement.js", + "end": [ + 1, + 36 + ] + } + ] + }, + "summary": "Replaced the 'g' identifier with the 'h' identifier", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "try-statement.js" + ], + "sha1": "3ca670bfa75c6a1708e8cbefcf5709baf85165b9", + "gitDir": "test/corpus/repos/javascript", + "sha2": "e509b6253596a24c3c4d49f53e7354d5415f6406" +} +,{ + "testCaseDescription": "javascript-try-statement-replacement-test", + "expectedResult": { + "changes": { + "try-statement.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 20 + ], + "name": "try-statement.js", + "end": [ + 1, + 21 + ] + }, + { + "start": [ + 1, + 20 + ], + "name": "try-statement.js", + "end": [ + 1, + 21 + ] + } + ] + }, + "summary": "Replaced the 'g' identifier with the 'h' identifier", + "tag": "JSONSummary" + }, + { + "span": { + "these": [ + { + "start": [ + 1, + 35 + ], + "name": "try-statement.js", + "end": [ + 1, + 36 + ] + }, + { + "start": [ + 1, + 35 + ], + "name": "try-statement.js", + "end": [ + 1, + 36 + ] + } + ] + }, + "summary": "Replaced the 'h' identifier with the 'g' identifier", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "try-statement.js" + ], + "sha1": "e509b6253596a24c3c4d49f53e7354d5415f6406", + "gitDir": "test/corpus/repos/javascript", + "sha2": "5539c67fd84c944d395de1bc1d849cdbc54508f4" +} +,{ + "testCaseDescription": "javascript-try-statement-delete-replacement-test", + "expectedResult": { + "changes": { + "try-statement.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "try-statement.js", + "end": [ + 1, + 39 + ] + } + }, + "summary": "Deleted the '{ f; }' try statement", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 1 + ], + "name": "try-statement.js", + "end": [ + 2, + 39 + ] + } + }, + "summary": "Deleted the '{ f; }' try statement", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "try-statement.js", + "end": [ + 2, + 39 + ] + } + }, + "summary": "Added the '{ f; }' try statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "try-statement.js" + ], + "sha1": "5539c67fd84c944d395de1bc1d849cdbc54508f4", + "gitDir": "test/corpus/repos/javascript", + "sha2": "159cfefd0e09b1a6cfdce7f7d7707aeff6837fd6" +} +,{ + "testCaseDescription": "javascript-try-statement-delete-test", + "expectedResult": { + "changes": { + "try-statement.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "try-statement.js", + "end": [ + 1, + 39 + ] + } + }, + "summary": "Deleted the '{ f; }' try statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "try-statement.js" + ], + "sha1": "159cfefd0e09b1a6cfdce7f7d7707aeff6837fd6", + "gitDir": "test/corpus/repos/javascript", + "sha2": "5063e245f1b1e2359cd10f7c01c184d103371810" +} +,{ + "testCaseDescription": "javascript-try-statement-delete-rest-test", + "expectedResult": { + "changes": { + "try-statement.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "try-statement.js", + "end": [ + 1, + 39 + ] + } + }, + "summary": "Deleted the '{ f; }' try statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "try-statement.js" + ], + "sha1": "5063e245f1b1e2359cd10f7c01c184d103371810", + "gitDir": "test/corpus/repos/javascript", + "sha2": "0578f24cf85fce35bd787e60e1b210b79f462858" +}] diff --git a/test/corpus/diff-summaries/javascript/type-operator.json b/test/corpus/diff-summaries/javascript/type-operator.json new file mode 100644 index 000000000..4c63329c7 --- /dev/null +++ b/test/corpus/diff-summaries/javascript/type-operator.json @@ -0,0 +1,282 @@ +[{ + "testCaseDescription": "javascript-type-operator-insert-test", + "expectedResult": { + "changes": { + "type-operator.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "type-operator.js", + "end": [ + 1, + 9 + ] + } + }, + "summary": "Added the 'typeof x' operator", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "type-operator.js" + ], + "sha1": "f01711cd334d609eaf2763a3694e94c771e37f3e", + "gitDir": "test/corpus/repos/javascript", + "sha2": "96aea0eed428b6b20488c222205f76ef2062a771" +} +,{ + "testCaseDescription": "javascript-type-operator-replacement-insert-test", + "expectedResult": { + "changes": { + "type-operator.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "type-operator.js", + "end": [ + 1, + 20 + ] + } + }, + "summary": "Added the 'x instanceof String' operator", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "type-operator.js", + "end": [ + 2, + 9 + ] + } + }, + "summary": "Added the 'typeof x' operator", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "type-operator.js" + ], + "sha1": "96aea0eed428b6b20488c222205f76ef2062a771", + "gitDir": "test/corpus/repos/javascript", + "sha2": "fa1b6db09e23a79415409fd5819d7a559b45adbb" +} +,{ + "testCaseDescription": "javascript-type-operator-delete-insert-test", + "expectedResult": { + "changes": { + "type-operator.js": [ + { + "span": { + "this": { + "start": [ + 1, + 14 + ], + "name": "type-operator.js", + "end": [ + 1, + 20 + ] + } + }, + "summary": "Deleted the 'String' identifier", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "type-operator.js" + ], + "sha1": "fa1b6db09e23a79415409fd5819d7a559b45adbb", + "gitDir": "test/corpus/repos/javascript", + "sha2": "73adba630bdf30c6bb43d2c586709818346f2ad0" +} +,{ + "testCaseDescription": "javascript-type-operator-replacement-test", + "expectedResult": { + "changes": { + "type-operator.js": [ + { + "span": { + "that": { + "start": [ + 1, + 14 + ], + "name": "type-operator.js", + "end": [ + 1, + 20 + ] + } + }, + "summary": "Added the 'String' identifier", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "type-operator.js" + ], + "sha1": "73adba630bdf30c6bb43d2c586709818346f2ad0", + "gitDir": "test/corpus/repos/javascript", + "sha2": "237bcf10f4bcbef5839bbb29d3a4985521581f5a" +} +,{ + "testCaseDescription": "javascript-type-operator-delete-replacement-test", + "expectedResult": { + "changes": { + "type-operator.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "type-operator.js", + "end": [ + 1, + 20 + ] + } + }, + "summary": "Deleted the 'x instanceof String' operator", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 1 + ], + "name": "type-operator.js", + "end": [ + 2, + 9 + ] + } + }, + "summary": "Deleted the 'typeof x' operator", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "type-operator.js", + "end": [ + 2, + 20 + ] + } + }, + "summary": "Added the 'x instanceof String' operator", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "type-operator.js" + ], + "sha1": "237bcf10f4bcbef5839bbb29d3a4985521581f5a", + "gitDir": "test/corpus/repos/javascript", + "sha2": "6b290f9e3aba6406475e0ffb0012267e34bb829d" +} +,{ + "testCaseDescription": "javascript-type-operator-delete-test", + "expectedResult": { + "changes": { + "type-operator.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "type-operator.js", + "end": [ + 1, + 9 + ] + } + }, + "summary": "Deleted the 'typeof x' operator", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "type-operator.js" + ], + "sha1": "6b290f9e3aba6406475e0ffb0012267e34bb829d", + "gitDir": "test/corpus/repos/javascript", + "sha2": "55f9cf52fbcb6cfdfc385b794e42e97d713a3ab2" +} +,{ + "testCaseDescription": "javascript-type-operator-delete-rest-test", + "expectedResult": { + "changes": { + "type-operator.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "type-operator.js", + "end": [ + 1, + 20 + ] + } + }, + "summary": "Deleted the 'x instanceof String' operator", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "type-operator.js" + ], + "sha1": "55f9cf52fbcb6cfdfc385b794e42e97d713a3ab2", + "gitDir": "test/corpus/repos/javascript", + "sha2": "c012557afb55395556a9209537f977c480c9cfa2" +}] diff --git a/test/corpus/diff-summaries/javascript/undefined.json b/test/corpus/diff-summaries/javascript/undefined.json new file mode 100644 index 000000000..5079ef9a4 --- /dev/null +++ b/test/corpus/diff-summaries/javascript/undefined.json @@ -0,0 +1,316 @@ +[{ + "testCaseDescription": "javascript-undefined-insert-test", + "expectedResult": { + "changes": { + "undefined.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "undefined.js", + "end": [ + 1, + 10 + ] + } + }, + "summary": "Added the 'undefined' identifier", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "undefined.js" + ], + "sha1": "c4cbb6a4ff71852691d643f686d8231c9a3989a4", + "gitDir": "test/corpus/repos/javascript", + "sha2": "fcd961d200815be0e5df9acbd6d7948232c2cff8" +} +,{ + "testCaseDescription": "javascript-undefined-replacement-insert-test", + "expectedResult": { + "changes": { + "undefined.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "undefined.js", + "end": [ + 1, + 18 + ] + } + }, + "summary": "Added the 'undefined' return statement", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "undefined.js", + "end": [ + 2, + 10 + ] + } + }, + "summary": "Added the 'undefined' identifier", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "undefined.js" + ], + "sha1": "fcd961d200815be0e5df9acbd6d7948232c2cff8", + "gitDir": "test/corpus/repos/javascript", + "sha2": "80316664f17060feb76cb3394afce3e4bb645e32" +} +,{ + "testCaseDescription": "javascript-undefined-delete-insert-test", + "expectedResult": { + "changes": { + "undefined.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "undefined.js", + "end": [ + 1, + 10 + ] + } + }, + "summary": "Added the 'undefined' identifier", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "undefined.js", + "end": [ + 1, + 18 + ] + } + }, + "summary": "Deleted the 'undefined' return statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "undefined.js" + ], + "sha1": "80316664f17060feb76cb3394afce3e4bb645e32", + "gitDir": "test/corpus/repos/javascript", + "sha2": "4f95a9bf9510322e9a6bf79636e45b35a0480a7c" +} +,{ + "testCaseDescription": "javascript-undefined-replacement-test", + "expectedResult": { + "changes": { + "undefined.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "undefined.js", + "end": [ + 1, + 18 + ] + } + }, + "summary": "Added the 'undefined' return statement", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "undefined.js", + "end": [ + 1, + 10 + ] + } + }, + "summary": "Deleted the 'undefined' identifier", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "undefined.js" + ], + "sha1": "4f95a9bf9510322e9a6bf79636e45b35a0480a7c", + "gitDir": "test/corpus/repos/javascript", + "sha2": "994be2b836b9ef3f76478f77e08fbcae2db003c2" +} +,{ + "testCaseDescription": "javascript-undefined-delete-replacement-test", + "expectedResult": { + "changes": { + "undefined.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "undefined.js", + "end": [ + 1, + 18 + ] + } + }, + "summary": "Deleted the 'undefined' return statement", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 1 + ], + "name": "undefined.js", + "end": [ + 2, + 10 + ] + } + }, + "summary": "Deleted the 'undefined' identifier", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "undefined.js", + "end": [ + 2, + 18 + ] + } + }, + "summary": "Added the 'undefined' return statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "undefined.js" + ], + "sha1": "994be2b836b9ef3f76478f77e08fbcae2db003c2", + "gitDir": "test/corpus/repos/javascript", + "sha2": "cd8d3a76c8a21b9cd938996afa84066513b5292c" +} +,{ + "testCaseDescription": "javascript-undefined-delete-test", + "expectedResult": { + "changes": { + "undefined.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "undefined.js", + "end": [ + 1, + 10 + ] + } + }, + "summary": "Deleted the 'undefined' identifier", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "undefined.js" + ], + "sha1": "cd8d3a76c8a21b9cd938996afa84066513b5292c", + "gitDir": "test/corpus/repos/javascript", + "sha2": "e202ac5fe4d20d33ab4e89cc92d6e0a70f685811" +} +,{ + "testCaseDescription": "javascript-undefined-delete-rest-test", + "expectedResult": { + "changes": { + "undefined.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "undefined.js", + "end": [ + 1, + 18 + ] + } + }, + "summary": "Deleted the 'undefined' return statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "undefined.js" + ], + "sha1": "e202ac5fe4d20d33ab4e89cc92d6e0a70f685811", + "gitDir": "test/corpus/repos/javascript", + "sha2": "230a472f82fce3b0be97b48298c0b3db54007c5c" +}] diff --git a/test/corpus/diff-summaries/javascript/var-declaration.json b/test/corpus/diff-summaries/javascript/var-declaration.json new file mode 100644 index 000000000..1d16fc958 --- /dev/null +++ b/test/corpus/diff-summaries/javascript/var-declaration.json @@ -0,0 +1,512 @@ +[{ + "testCaseDescription": "javascript-var-declaration-insert-test", + "expectedResult": { + "changes": { + "var-declaration.js": [ + { + "span": { + "that": { + "start": [ + 1, + 5 + ], + "name": "var-declaration.js", + "end": [ + 1, + 10 + ] + } + }, + "summary": "Added the 'x' variable", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "var-declaration.js" + ], + "sha1": "9f1361ad761d81ff9d3b968ebeefa0f9640ae0ca", + "gitDir": "test/corpus/repos/javascript", + "sha2": "a8c2f82710f1241c44e40cee6ca80a095ea851e3" +} +,{ + "testCaseDescription": "javascript-var-declaration-replacement-insert-test", + "expectedResult": { + "changes": { + "var-declaration.js": [ + { + "span": { + "that": { + "start": [ + 1, + 5 + ], + "name": "var-declaration.js", + "end": [ + 1, + 6 + ] + } + }, + "summary": "Added the 'x' variable", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 1, + 8 + ], + "name": "var-declaration.js", + "end": [ + 1, + 14 + ] + } + }, + "summary": "Added the 'y' variable", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 1, + 16 + ], + "name": "var-declaration.js", + "end": [ + 1, + 17 + ] + } + }, + "summary": "Added the 'z' variable", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 5 + ], + "name": "var-declaration.js", + "end": [ + 2, + 10 + ] + } + }, + "summary": "Added the 'x' variable", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "var-declaration.js" + ], + "sha1": "a8c2f82710f1241c44e40cee6ca80a095ea851e3", + "gitDir": "test/corpus/repos/javascript", + "sha2": "43e3fc6013d5fc2f1db341fde7f4fe9ea060e7e1" +} +,{ + "testCaseDescription": "javascript-var-declaration-delete-insert-test", + "expectedResult": { + "changes": { + "var-declaration.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 5 + ], + "name": "var-declaration.js", + "end": [ + 1, + 6 + ] + }, + { + "start": [ + 1, + 5 + ], + "name": "var-declaration.js", + "end": [ + 1, + 10 + ] + } + ] + }, + "summary": "Replaced the 'x' variable with the 'x' variable", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 1, + 8 + ], + "name": "var-declaration.js", + "end": [ + 1, + 14 + ] + } + }, + "summary": "Deleted the 'y' variable", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 1, + 16 + ], + "name": "var-declaration.js", + "end": [ + 1, + 17 + ] + } + }, + "summary": "Deleted the 'z' variable", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "var-declaration.js" + ], + "sha1": "43e3fc6013d5fc2f1db341fde7f4fe9ea060e7e1", + "gitDir": "test/corpus/repos/javascript", + "sha2": "c3ea199c46ebfe632dad05ad20bdfb776835a9d5" +} +,{ + "testCaseDescription": "javascript-var-declaration-replacement-test", + "expectedResult": { + "changes": { + "var-declaration.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 5 + ], + "name": "var-declaration.js", + "end": [ + 1, + 10 + ] + }, + { + "start": [ + 1, + 5 + ], + "name": "var-declaration.js", + "end": [ + 1, + 6 + ] + } + ] + }, + "summary": "Replaced the 'x' variable with the 'x' variable", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 1, + 8 + ], + "name": "var-declaration.js", + "end": [ + 1, + 14 + ] + } + }, + "summary": "Added the 'y' variable", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 1, + 16 + ], + "name": "var-declaration.js", + "end": [ + 1, + 17 + ] + } + }, + "summary": "Added the 'z' variable", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "var-declaration.js" + ], + "sha1": "c3ea199c46ebfe632dad05ad20bdfb776835a9d5", + "gitDir": "test/corpus/repos/javascript", + "sha2": "70e0141884fe614c029ceab9cabb24ac689f8c50" +} +,{ + "testCaseDescription": "javascript-var-declaration-delete-replacement-test", + "expectedResult": { + "changes": { + "var-declaration.js": [ + { + "span": { + "this": { + "start": [ + 1, + 5 + ], + "name": "var-declaration.js", + "end": [ + 1, + 6 + ] + } + }, + "summary": "Deleted the 'x' variable", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 1, + 8 + ], + "name": "var-declaration.js", + "end": [ + 1, + 14 + ] + } + }, + "summary": "Deleted the 'y' variable", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 1, + 16 + ], + "name": "var-declaration.js", + "end": [ + 1, + 17 + ] + } + }, + "summary": "Deleted the 'z' variable", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 5 + ], + "name": "var-declaration.js", + "end": [ + 2, + 10 + ] + } + }, + "summary": "Deleted the 'x' variable", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 5 + ], + "name": "var-declaration.js", + "end": [ + 2, + 6 + ] + } + }, + "summary": "Added the 'x' variable", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 8 + ], + "name": "var-declaration.js", + "end": [ + 2, + 14 + ] + } + }, + "summary": "Added the 'y' variable", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 16 + ], + "name": "var-declaration.js", + "end": [ + 2, + 17 + ] + } + }, + "summary": "Added the 'z' variable", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "var-declaration.js" + ], + "sha1": "70e0141884fe614c029ceab9cabb24ac689f8c50", + "gitDir": "test/corpus/repos/javascript", + "sha2": "f4ebb1027bebfbeacd6fbb4a6e1f16e2423ee62e" +} +,{ + "testCaseDescription": "javascript-var-declaration-delete-test", + "expectedResult": { + "changes": { + "var-declaration.js": [ + { + "span": { + "this": { + "start": [ + 1, + 5 + ], + "name": "var-declaration.js", + "end": [ + 1, + 10 + ] + } + }, + "summary": "Deleted the 'x' variable", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "var-declaration.js" + ], + "sha1": "f4ebb1027bebfbeacd6fbb4a6e1f16e2423ee62e", + "gitDir": "test/corpus/repos/javascript", + "sha2": "e18b5c0b82a5bdf95e7977d7947e44d872d5abfc" +} +,{ + "testCaseDescription": "javascript-var-declaration-delete-rest-test", + "expectedResult": { + "changes": { + "var-declaration.js": [ + { + "span": { + "this": { + "start": [ + 1, + 5 + ], + "name": "var-declaration.js", + "end": [ + 1, + 6 + ] + } + }, + "summary": "Deleted the 'x' variable", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 1, + 8 + ], + "name": "var-declaration.js", + "end": [ + 1, + 14 + ] + } + }, + "summary": "Deleted the 'y' variable", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 1, + 16 + ], + "name": "var-declaration.js", + "end": [ + 1, + 17 + ] + } + }, + "summary": "Deleted the 'z' variable", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "var-declaration.js" + ], + "sha1": "e18b5c0b82a5bdf95e7977d7947e44d872d5abfc", + "gitDir": "test/corpus/repos/javascript", + "sha2": "a67c36dee6afa77efd8005ab23227f683239d35e" +}] diff --git a/test/corpus/diff-summaries/javascript/variable.json b/test/corpus/diff-summaries/javascript/variable.json new file mode 100644 index 000000000..e609d95e0 --- /dev/null +++ b/test/corpus/diff-summaries/javascript/variable.json @@ -0,0 +1,308 @@ +[{ + "testCaseDescription": "javascript-variable-insert-test", + "expectedResult": { + "changes": { + "variable.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "variable.js", + "end": [ + 1, + 7 + ] + } + }, + "summary": "Added the 'theVar' identifier", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "variable.js" + ], + "sha1": "4df21e328803748f18b7cd64862f776a275b1448", + "gitDir": "test/corpus/repos/javascript", + "sha2": "a3840d75920054be5279d78807096889c4c989c9" +} +,{ + "testCaseDescription": "javascript-variable-replacement-insert-test", + "expectedResult": { + "changes": { + "variable.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "variable.js", + "end": [ + 1, + 8 + ] + } + }, + "summary": "Added the 'theVar2' identifier", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "variable.js", + "end": [ + 2, + 7 + ] + } + }, + "summary": "Added the 'theVar' identifier", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "variable.js" + ], + "sha1": "a3840d75920054be5279d78807096889c4c989c9", + "gitDir": "test/corpus/repos/javascript", + "sha2": "a42caa0fda1bdb5b316d718758cbf4a51861c2b2" +} +,{ + "testCaseDescription": "javascript-variable-delete-insert-test", + "expectedResult": { + "changes": { + "variable.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 1 + ], + "name": "variable.js", + "end": [ + 1, + 8 + ] + }, + { + "start": [ + 1, + 1 + ], + "name": "variable.js", + "end": [ + 1, + 7 + ] + } + ] + }, + "summary": "Replaced the 'theVar2' identifier with the 'theVar' identifier", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "variable.js" + ], + "sha1": "a42caa0fda1bdb5b316d718758cbf4a51861c2b2", + "gitDir": "test/corpus/repos/javascript", + "sha2": "16873fbd755c8e72f25d8aa042c4d2f837cfd23f" +} +,{ + "testCaseDescription": "javascript-variable-replacement-test", + "expectedResult": { + "changes": { + "variable.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 1 + ], + "name": "variable.js", + "end": [ + 1, + 7 + ] + }, + { + "start": [ + 1, + 1 + ], + "name": "variable.js", + "end": [ + 1, + 8 + ] + } + ] + }, + "summary": "Replaced the 'theVar' identifier with the 'theVar2' identifier", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "variable.js" + ], + "sha1": "16873fbd755c8e72f25d8aa042c4d2f837cfd23f", + "gitDir": "test/corpus/repos/javascript", + "sha2": "0d06b024a50e68aa79d056bc76fdec5e6e640ef3" +} +,{ + "testCaseDescription": "javascript-variable-delete-replacement-test", + "expectedResult": { + "changes": { + "variable.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "variable.js", + "end": [ + 1, + 8 + ] + } + }, + "summary": "Deleted the 'theVar2' identifier", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 1 + ], + "name": "variable.js", + "end": [ + 2, + 7 + ] + } + }, + "summary": "Deleted the 'theVar' identifier", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "variable.js", + "end": [ + 2, + 8 + ] + } + }, + "summary": "Added the 'theVar2' identifier", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "variable.js" + ], + "sha1": "0d06b024a50e68aa79d056bc76fdec5e6e640ef3", + "gitDir": "test/corpus/repos/javascript", + "sha2": "191cfbfac32bb38d5d4b5bf0c008c473e8302fd4" +} +,{ + "testCaseDescription": "javascript-variable-delete-test", + "expectedResult": { + "changes": { + "variable.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "variable.js", + "end": [ + 1, + 7 + ] + } + }, + "summary": "Deleted the 'theVar' identifier", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "variable.js" + ], + "sha1": "191cfbfac32bb38d5d4b5bf0c008c473e8302fd4", + "gitDir": "test/corpus/repos/javascript", + "sha2": "690d29ead8ccc9c917669062891777ba61074c53" +} +,{ + "testCaseDescription": "javascript-variable-delete-rest-test", + "expectedResult": { + "changes": { + "variable.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "variable.js", + "end": [ + 1, + 8 + ] + } + }, + "summary": "Deleted the 'theVar2' identifier", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "variable.js" + ], + "sha1": "690d29ead8ccc9c917669062891777ba61074c53", + "gitDir": "test/corpus/repos/javascript", + "sha2": "8bed39ae9a7d7acce7400df7173470825fa46cb0" +}] diff --git a/test/corpus/diff-summaries/javascript/void-operator.json b/test/corpus/diff-summaries/javascript/void-operator.json new file mode 100644 index 000000000..af2b96df7 --- /dev/null +++ b/test/corpus/diff-summaries/javascript/void-operator.json @@ -0,0 +1,308 @@ +[{ + "testCaseDescription": "javascript-void-operator-insert-test", + "expectedResult": { + "changes": { + "void-operator.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "void-operator.js", + "end": [ + 1, + 9 + ] + } + }, + "summary": "Added the 'void b()' operator", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "void-operator.js" + ], + "sha1": "4c9359461db3f23921b2af834190b8c9966fa455", + "gitDir": "test/corpus/repos/javascript", + "sha2": "0d445752b33202f03c21c0f575075b54b75d594f" +} +,{ + "testCaseDescription": "javascript-void-operator-replacement-insert-test", + "expectedResult": { + "changes": { + "void-operator.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "void-operator.js", + "end": [ + 1, + 9 + ] + } + }, + "summary": "Added the 'void c()' operator", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "void-operator.js", + "end": [ + 2, + 9 + ] + } + }, + "summary": "Added the 'void b()' operator", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "void-operator.js" + ], + "sha1": "0d445752b33202f03c21c0f575075b54b75d594f", + "gitDir": "test/corpus/repos/javascript", + "sha2": "6084c7a622486376a750e062b57485ba15ce33d7" +} +,{ + "testCaseDescription": "javascript-void-operator-delete-insert-test", + "expectedResult": { + "changes": { + "void-operator.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 6 + ], + "name": "void-operator.js", + "end": [ + 1, + 7 + ] + }, + { + "start": [ + 1, + 6 + ], + "name": "void-operator.js", + "end": [ + 1, + 7 + ] + } + ] + }, + "summary": "Replaced the 'c' identifier with the 'b' identifier in the b() function call", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "void-operator.js" + ], + "sha1": "6084c7a622486376a750e062b57485ba15ce33d7", + "gitDir": "test/corpus/repos/javascript", + "sha2": "bd8157de0083725f324c0b07300ab40b761faf9a" +} +,{ + "testCaseDescription": "javascript-void-operator-replacement-test", + "expectedResult": { + "changes": { + "void-operator.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 6 + ], + "name": "void-operator.js", + "end": [ + 1, + 7 + ] + }, + { + "start": [ + 1, + 6 + ], + "name": "void-operator.js", + "end": [ + 1, + 7 + ] + } + ] + }, + "summary": "Replaced the 'b' identifier with the 'c' identifier in the c() function call", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "void-operator.js" + ], + "sha1": "bd8157de0083725f324c0b07300ab40b761faf9a", + "gitDir": "test/corpus/repos/javascript", + "sha2": "822356e36fe70b7e90fde40d96cf3ea636f80238" +} +,{ + "testCaseDescription": "javascript-void-operator-delete-replacement-test", + "expectedResult": { + "changes": { + "void-operator.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "void-operator.js", + "end": [ + 1, + 9 + ] + } + }, + "summary": "Deleted the 'void c()' operator", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 1 + ], + "name": "void-operator.js", + "end": [ + 2, + 9 + ] + } + }, + "summary": "Deleted the 'void b()' operator", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "void-operator.js", + "end": [ + 2, + 9 + ] + } + }, + "summary": "Added the 'void c()' operator", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "void-operator.js" + ], + "sha1": "822356e36fe70b7e90fde40d96cf3ea636f80238", + "gitDir": "test/corpus/repos/javascript", + "sha2": "d7082a08524da8cf4d379c767819b756b9970d34" +} +,{ + "testCaseDescription": "javascript-void-operator-delete-test", + "expectedResult": { + "changes": { + "void-operator.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "void-operator.js", + "end": [ + 1, + 9 + ] + } + }, + "summary": "Deleted the 'void b()' operator", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "void-operator.js" + ], + "sha1": "d7082a08524da8cf4d379c767819b756b9970d34", + "gitDir": "test/corpus/repos/javascript", + "sha2": "19112b8b21566d018b1fbb073d3e3211067d653c" +} +,{ + "testCaseDescription": "javascript-void-operator-delete-rest-test", + "expectedResult": { + "changes": { + "void-operator.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "void-operator.js", + "end": [ + 1, + 9 + ] + } + }, + "summary": "Deleted the 'void c()' operator", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "void-operator.js" + ], + "sha1": "19112b8b21566d018b1fbb073d3e3211067d653c", + "gitDir": "test/corpus/repos/javascript", + "sha2": "de1bc70d66645688aab217b87e9d472a34e42bd1" +}] diff --git a/test/corpus/diff-summaries/javascript/while-statement.json b/test/corpus/diff-summaries/javascript/while-statement.json new file mode 100644 index 000000000..e6c45c7b6 --- /dev/null +++ b/test/corpus/diff-summaries/javascript/while-statement.json @@ -0,0 +1,368 @@ +[{ + "testCaseDescription": "javascript-while-statement-insert-test", + "expectedResult": { + "changes": { + "while-statement.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "while-statement.js", + "end": [ + 1, + 19 + ] + } + }, + "summary": "Added the 'a' while statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "while-statement.js" + ], + "sha1": "4baec39517b6fe2e913b63502b66c0f5bb4ad2cc", + "gitDir": "test/corpus/repos/javascript", + "sha2": "9e37955434527f912890ae216acc3ae299622141" +} +,{ + "testCaseDescription": "javascript-while-statement-replacement-insert-test", + "expectedResult": { + "changes": { + "while-statement.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "while-statement.js", + "end": [ + 1, + 19 + ] + } + }, + "summary": "Added the 'b' while statement", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "while-statement.js", + "end": [ + 2, + 19 + ] + } + }, + "summary": "Added the 'a' while statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "while-statement.js" + ], + "sha1": "9e37955434527f912890ae216acc3ae299622141", + "gitDir": "test/corpus/repos/javascript", + "sha2": "f7b70918071a6521eaef2c5be1b3ac9720841446" +} +,{ + "testCaseDescription": "javascript-while-statement-delete-insert-test", + "expectedResult": { + "changes": { + "while-statement.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 8 + ], + "name": "while-statement.js", + "end": [ + 1, + 9 + ] + }, + { + "start": [ + 1, + 8 + ], + "name": "while-statement.js", + "end": [ + 1, + 9 + ] + } + ] + }, + "summary": "Replaced the 'b' identifier with the 'a' identifier", + "tag": "JSONSummary" + }, + { + "span": { + "these": [ + { + "start": [ + 1, + 13 + ], + "name": "while-statement.js", + "end": [ + 1, + 14 + ] + }, + { + "start": [ + 1, + 13 + ], + "name": "while-statement.js", + "end": [ + 1, + 14 + ] + } + ] + }, + "summary": "Replaced the 'a' identifier with the 'b' identifier in the b() function call", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "while-statement.js" + ], + "sha1": "f7b70918071a6521eaef2c5be1b3ac9720841446", + "gitDir": "test/corpus/repos/javascript", + "sha2": "29c8ebffa11db7289ab51f57efd175f77bd733bd" +} +,{ + "testCaseDescription": "javascript-while-statement-replacement-test", + "expectedResult": { + "changes": { + "while-statement.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 8 + ], + "name": "while-statement.js", + "end": [ + 1, + 9 + ] + }, + { + "start": [ + 1, + 8 + ], + "name": "while-statement.js", + "end": [ + 1, + 9 + ] + } + ] + }, + "summary": "Replaced the 'a' identifier with the 'b' identifier", + "tag": "JSONSummary" + }, + { + "span": { + "these": [ + { + "start": [ + 1, + 13 + ], + "name": "while-statement.js", + "end": [ + 1, + 14 + ] + }, + { + "start": [ + 1, + 13 + ], + "name": "while-statement.js", + "end": [ + 1, + 14 + ] + } + ] + }, + "summary": "Replaced the 'b' identifier with the 'a' identifier in the a() function call", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "while-statement.js" + ], + "sha1": "29c8ebffa11db7289ab51f57efd175f77bd733bd", + "gitDir": "test/corpus/repos/javascript", + "sha2": "f4d194f2e3d461c76413a90b0d2313ca005b9dfc" +} +,{ + "testCaseDescription": "javascript-while-statement-delete-replacement-test", + "expectedResult": { + "changes": { + "while-statement.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "while-statement.js", + "end": [ + 1, + 19 + ] + } + }, + "summary": "Deleted the 'b' while statement", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 1 + ], + "name": "while-statement.js", + "end": [ + 2, + 19 + ] + } + }, + "summary": "Deleted the 'a' while statement", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "while-statement.js", + "end": [ + 2, + 19 + ] + } + }, + "summary": "Added the 'b' while statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "while-statement.js" + ], + "sha1": "f4d194f2e3d461c76413a90b0d2313ca005b9dfc", + "gitDir": "test/corpus/repos/javascript", + "sha2": "a04a222d36c3f3af7c33b093cc2478968ae3651e" +} +,{ + "testCaseDescription": "javascript-while-statement-delete-test", + "expectedResult": { + "changes": { + "while-statement.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "while-statement.js", + "end": [ + 1, + 19 + ] + } + }, + "summary": "Deleted the 'a' while statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "while-statement.js" + ], + "sha1": "a04a222d36c3f3af7c33b093cc2478968ae3651e", + "gitDir": "test/corpus/repos/javascript", + "sha2": "72f779a1fb746477acef381391603e40efb5ff43" +} +,{ + "testCaseDescription": "javascript-while-statement-delete-rest-test", + "expectedResult": { + "changes": { + "while-statement.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "while-statement.js", + "end": [ + 1, + 19 + ] + } + }, + "summary": "Deleted the 'b' while statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "while-statement.js" + ], + "sha1": "72f779a1fb746477acef381391603e40efb5ff43", + "gitDir": "test/corpus/repos/javascript", + "sha2": "2991c8cdbe1144d3164c0fc0075cb5388e06583b" +}] diff --git a/test/corpus/repos/javascript b/test/corpus/repos/javascript index 870c7e629..6c18f0fbe 160000 --- a/test/corpus/repos/javascript +++ b/test/corpus/repos/javascript @@ -1 +1 @@ -Subproject commit 870c7e629a76e123abf0a4f8095499e596838bfd +Subproject commit 6c18f0fbe80bb95f6642653913241b9065181591 From a08cad66d0057c9bd89dc7415c4a15269e604365 Mon Sep 17 00:00:00 2001 From: joshvera Date: Tue, 11 Oct 2016 11:13:44 -0400 Subject: [PATCH 16/27] ++javascript --- test/corpus/repos/javascript | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/test/corpus/repos/javascript b/test/corpus/repos/javascript index 6c18f0fbe..25d0dca67 160000 --- a/test/corpus/repos/javascript +++ b/test/corpus/repos/javascript @@ -1 +1 @@ -Subproject commit 6c18f0fbe80bb95f6642653913241b9065181591 +Subproject commit 25d0dca67cfd26a4d408ec7cc751b428dd7d0451 From fbb6ddbff4db7b46b05514c3a533072db4d1d984 Mon Sep 17 00:00:00 2001 From: joshvera Date: Tue, 11 Oct 2016 11:26:57 -0400 Subject: [PATCH 17/27] Bump tests --- .../javascript/anonymous-function.json | 28 +++++++++---------- .../anonymous-parameterless-function.json | 28 +++++++++---------- .../diff-summaries/javascript/array.json | 28 +++++++++---------- .../javascript/arrow-function.json | 28 +++++++++---------- .../diff-summaries/javascript/assignment.json | 28 +++++++++---------- .../javascript/bitwise-operator.json | 28 +++++++++---------- .../javascript/boolean-operator.json | 28 +++++++++---------- .../javascript/chained-callbacks.json | 28 +++++++++---------- .../javascript/chained-property-access.json | 28 +++++++++---------- .../diff-summaries/javascript/class.json | 28 +++++++++---------- .../javascript/comma-operator.json | 28 +++++++++---------- .../diff-summaries/javascript/comment.json | 28 +++++++++---------- .../javascript/constructor-call.json | 28 +++++++++---------- .../javascript/delete-operator.json | 28 +++++++++---------- .../javascript/do-while-statement.json | 28 +++++++++---------- .../diff-summaries/javascript/false.json | 28 +++++++++---------- .../javascript/for-in-statement.json | 28 +++++++++---------- .../for-loop-with-in-statement.json | 28 +++++++++---------- .../javascript/for-of-statement.json | 28 +++++++++---------- .../javascript/for-statement.json | 28 +++++++++---------- .../javascript/function-call-args.json | 28 +++++++++---------- .../javascript/function-call.json | 28 +++++++++---------- .../diff-summaries/javascript/function.json | 28 +++++++++---------- .../javascript/generator-function.json | 28 +++++++++---------- .../diff-summaries/javascript/identifier.json | 28 +++++++++---------- .../diff-summaries/javascript/if-else.json | 28 +++++++++---------- test/corpus/diff-summaries/javascript/if.json | 28 +++++++++---------- .../javascript/math-assignment-operator.json | 28 +++++++++---------- .../javascript/math-operator.json | 28 +++++++++---------- .../javascript/member-access-assignment.json | 28 +++++++++---------- .../javascript/member-access.json | 28 +++++++++---------- .../javascript/method-call.json | 28 +++++++++---------- .../javascript/named-function.json | 28 +++++++++---------- .../javascript/nested-functions.json | 28 +++++++++---------- .../diff-summaries/javascript/null.json | 28 +++++++++---------- .../diff-summaries/javascript/number.json | 28 +++++++++---------- .../javascript/object-with-methods.json | 28 +++++++++---------- .../diff-summaries/javascript/object.json | 28 +++++++++---------- .../diff-summaries/javascript/regex.json | 28 +++++++++---------- .../javascript/relational-operator.json | 28 +++++++++---------- .../javascript/return-statement.json | 28 +++++++++---------- .../diff-summaries/javascript/string.json | 28 +++++++++---------- .../subscript-access-assignment.json | 28 +++++++++---------- .../javascript/subscript-access-string.json | 28 +++++++++---------- .../javascript/subscript-access-variable.json | 28 +++++++++---------- .../javascript/switch-statement.json | 28 +++++++++---------- .../javascript/template-string.json | 28 +++++++++---------- .../diff-summaries/javascript/ternary.json | 28 +++++++++---------- .../javascript/this-expression.json | 28 +++++++++---------- .../javascript/throw-statement.json | 28 +++++++++---------- .../diff-summaries/javascript/true.json | 28 +++++++++---------- .../javascript/try-statement.json | 28 +++++++++---------- .../javascript/type-operator.json | 28 +++++++++---------- .../diff-summaries/javascript/undefined.json | 28 +++++++++---------- .../javascript/var-declaration.json | 28 +++++++++---------- .../diff-summaries/javascript/variable.json | 28 +++++++++---------- .../javascript/void-operator.json | 28 +++++++++---------- .../javascript/while-statement.json | 28 +++++++++---------- test/corpus/repos/javascript | 2 +- 59 files changed, 813 insertions(+), 813 deletions(-) diff --git a/test/corpus/diff-summaries/javascript/anonymous-function.json b/test/corpus/diff-summaries/javascript/anonymous-function.json index f034da116..c2334311a 100644 --- a/test/corpus/diff-summaries/javascript/anonymous-function.json +++ b/test/corpus/diff-summaries/javascript/anonymous-function.json @@ -27,9 +27,9 @@ "filePaths": [ "anonymous-function.js" ], - "sha1": "a0404e9e7b61466d953a033ff444c10691cea549", + "sha1": "2f014a3eddb509376944a4938ace7c0eb952308d", "gitDir": "test/corpus/repos/javascript", - "sha2": "1961f9a7fb461c1318e0b6c46b61fc897fa1560b" + "sha2": "a8fcbf2e63b9096c5fea21b0811bc0017e48a5b5" } ,{ "testCaseDescription": "javascript-anonymous-function-replacement-insert-test", @@ -77,9 +77,9 @@ "filePaths": [ "anonymous-function.js" ], - "sha1": "1961f9a7fb461c1318e0b6c46b61fc897fa1560b", + "sha1": "a8fcbf2e63b9096c5fea21b0811bc0017e48a5b5", "gitDir": "test/corpus/repos/javascript", - "sha2": "a87c5f91d1af023c750e53541117a0d019b49ed9" + "sha2": "9f454c8396c898ded02c426f24bb578fde429fda" } ,{ "testCaseDescription": "javascript-anonymous-function-delete-insert-test", @@ -213,9 +213,9 @@ "filePaths": [ "anonymous-function.js" ], - "sha1": "a87c5f91d1af023c750e53541117a0d019b49ed9", + "sha1": "9f454c8396c898ded02c426f24bb578fde429fda", "gitDir": "test/corpus/repos/javascript", - "sha2": "ae9ec1df052f843a7f32f581fa51fecfee985b33" + "sha2": "76497977ea3f866b200735314c4cd3d3f869d592" } ,{ "testCaseDescription": "javascript-anonymous-function-replacement-test", @@ -349,9 +349,9 @@ "filePaths": [ "anonymous-function.js" ], - "sha1": "ae9ec1df052f843a7f32f581fa51fecfee985b33", + "sha1": "76497977ea3f866b200735314c4cd3d3f869d592", "gitDir": "test/corpus/repos/javascript", - "sha2": "97a65badadc090ac8798ea1710c611c32c6521fa" + "sha2": "7e5e1a029d13f2b597d893a9238798d2be3fe2e7" } ,{ "testCaseDescription": "javascript-anonymous-function-delete-replacement-test", @@ -416,9 +416,9 @@ "filePaths": [ "anonymous-function.js" ], - "sha1": "97a65badadc090ac8798ea1710c611c32c6521fa", + "sha1": "7e5e1a029d13f2b597d893a9238798d2be3fe2e7", "gitDir": "test/corpus/repos/javascript", - "sha2": "7aa2ca6547621b95a8648317f5824a147b42ab6c" + "sha2": "b45156e4dd71a0fa4fa8593967953f50792c4c4e" } ,{ "testCaseDescription": "javascript-anonymous-function-delete-test", @@ -449,9 +449,9 @@ "filePaths": [ "anonymous-function.js" ], - "sha1": "7aa2ca6547621b95a8648317f5824a147b42ab6c", + "sha1": "b45156e4dd71a0fa4fa8593967953f50792c4c4e", "gitDir": "test/corpus/repos/javascript", - "sha2": "77a404dd843047629e7c0f3d1e7e59b97dc14278" + "sha2": "4707e7becd4c216977b13fcc4e1e1118baa7fc0f" } ,{ "testCaseDescription": "javascript-anonymous-function-delete-rest-test", @@ -482,7 +482,7 @@ "filePaths": [ "anonymous-function.js" ], - "sha1": "77a404dd843047629e7c0f3d1e7e59b97dc14278", + "sha1": "4707e7becd4c216977b13fcc4e1e1118baa7fc0f", "gitDir": "test/corpus/repos/javascript", - "sha2": "cbe8e933001ed566c983447bd68c559b8a0ce299" + "sha2": "243878b6c3b6f74b080ea4f2188dffe5f3ca5517" }] diff --git a/test/corpus/diff-summaries/javascript/anonymous-parameterless-function.json b/test/corpus/diff-summaries/javascript/anonymous-parameterless-function.json index 3b58d4cd4..19de8c0e6 100644 --- a/test/corpus/diff-summaries/javascript/anonymous-parameterless-function.json +++ b/test/corpus/diff-summaries/javascript/anonymous-parameterless-function.json @@ -27,9 +27,9 @@ "filePaths": [ "anonymous-parameterless-function.js" ], - "sha1": "cbe8e933001ed566c983447bd68c559b8a0ce299", + "sha1": "243878b6c3b6f74b080ea4f2188dffe5f3ca5517", "gitDir": "test/corpus/repos/javascript", - "sha2": "c04c265e97a0a02caf81a65d81ddd315928ebfd6" + "sha2": "514143027c392e84ae25e96805949caab52f1561" } ,{ "testCaseDescription": "javascript-anonymous-parameterless-function-replacement-insert-test", @@ -77,9 +77,9 @@ "filePaths": [ "anonymous-parameterless-function.js" ], - "sha1": "c04c265e97a0a02caf81a65d81ddd315928ebfd6", + "sha1": "514143027c392e84ae25e96805949caab52f1561", "gitDir": "test/corpus/repos/javascript", - "sha2": "d7a616f801c122aff974bdd825ffe1bb51c5a8e8" + "sha2": "b563ad1a2f183b9aa3eeaebd30a4d8b19b9a7a11" } ,{ "testCaseDescription": "javascript-anonymous-parameterless-function-delete-insert-test", @@ -123,9 +123,9 @@ "filePaths": [ "anonymous-parameterless-function.js" ], - "sha1": "d7a616f801c122aff974bdd825ffe1bb51c5a8e8", + "sha1": "b563ad1a2f183b9aa3eeaebd30a4d8b19b9a7a11", "gitDir": "test/corpus/repos/javascript", - "sha2": "14d2f7d564ac1e8c0d2ca9960c9f42fcaf70f1fa" + "sha2": "f44fd8faf60a62826c1149b797d4c6de9758c2cb" } ,{ "testCaseDescription": "javascript-anonymous-parameterless-function-replacement-test", @@ -169,9 +169,9 @@ "filePaths": [ "anonymous-parameterless-function.js" ], - "sha1": "14d2f7d564ac1e8c0d2ca9960c9f42fcaf70f1fa", + "sha1": "f44fd8faf60a62826c1149b797d4c6de9758c2cb", "gitDir": "test/corpus/repos/javascript", - "sha2": "24aaf302c042840e41e709b2d1b4b9310c1f3dac" + "sha2": "76bb7e8592f8fced41f61f81538c202b3c5fb3df" } ,{ "testCaseDescription": "javascript-anonymous-parameterless-function-delete-replacement-test", @@ -236,9 +236,9 @@ "filePaths": [ "anonymous-parameterless-function.js" ], - "sha1": "24aaf302c042840e41e709b2d1b4b9310c1f3dac", + "sha1": "76bb7e8592f8fced41f61f81538c202b3c5fb3df", "gitDir": "test/corpus/repos/javascript", - "sha2": "dc90b671f97861fbcd6f3589c51c7d533183fd48" + "sha2": "bcc25dd39ebe005c0282ddea0611c7039fc70ec8" } ,{ "testCaseDescription": "javascript-anonymous-parameterless-function-delete-test", @@ -269,9 +269,9 @@ "filePaths": [ "anonymous-parameterless-function.js" ], - "sha1": "dc90b671f97861fbcd6f3589c51c7d533183fd48", + "sha1": "bcc25dd39ebe005c0282ddea0611c7039fc70ec8", "gitDir": "test/corpus/repos/javascript", - "sha2": "40ac908bb69f7662e5fe092a8c3f5af80a5ea195" + "sha2": "425b3995f55840eef8727deb5c9b6bf82b47dfbe" } ,{ "testCaseDescription": "javascript-anonymous-parameterless-function-delete-rest-test", @@ -302,7 +302,7 @@ "filePaths": [ "anonymous-parameterless-function.js" ], - "sha1": "40ac908bb69f7662e5fe092a8c3f5af80a5ea195", + "sha1": "425b3995f55840eef8727deb5c9b6bf82b47dfbe", "gitDir": "test/corpus/repos/javascript", - "sha2": "a7028eef7c56f7ba5c5dda0faadcfffe205d5a40" + "sha2": "96217c240d7773372a78d2a23601a4a97459fcad" }] diff --git a/test/corpus/diff-summaries/javascript/array.json b/test/corpus/diff-summaries/javascript/array.json index bb27e911c..3a4a601fc 100644 --- a/test/corpus/diff-summaries/javascript/array.json +++ b/test/corpus/diff-summaries/javascript/array.json @@ -27,9 +27,9 @@ "filePaths": [ "array.js" ], - "sha1": "6c3b6d5c7d426a657e90d97cdfd248b2453bc087", + "sha1": "407eb0654feb336967cfa7e099e277590d97ea6d", "gitDir": "test/corpus/repos/javascript", - "sha2": "3445abbd9210b7d4d23872fdf2614b77c3e464bd" + "sha2": "96df91034072bb590ad228fdedccbd70de25ad8a" } ,{ "testCaseDescription": "javascript-array-replacement-insert-test", @@ -77,9 +77,9 @@ "filePaths": [ "array.js" ], - "sha1": "3445abbd9210b7d4d23872fdf2614b77c3e464bd", + "sha1": "96df91034072bb590ad228fdedccbd70de25ad8a", "gitDir": "test/corpus/repos/javascript", - "sha2": "7d3cd095cf340ccda50bd7dae0405288a27d6a28" + "sha2": "ba51e3698922b41ac81594e59a66d25d0a1f563c" } ,{ "testCaseDescription": "javascript-array-delete-insert-test", @@ -110,9 +110,9 @@ "filePaths": [ "array.js" ], - "sha1": "7d3cd095cf340ccda50bd7dae0405288a27d6a28", + "sha1": "ba51e3698922b41ac81594e59a66d25d0a1f563c", "gitDir": "test/corpus/repos/javascript", - "sha2": "7d1d0e7c6052a06a9bf764a04ca06acff78dffca" + "sha2": "9c4cdc5d327ec94d28bc7900690e4eb5ecfaa6a9" } ,{ "testCaseDescription": "javascript-array-replacement-test", @@ -143,9 +143,9 @@ "filePaths": [ "array.js" ], - "sha1": "7d1d0e7c6052a06a9bf764a04ca06acff78dffca", + "sha1": "9c4cdc5d327ec94d28bc7900690e4eb5ecfaa6a9", "gitDir": "test/corpus/repos/javascript", - "sha2": "aac7a79ab7aecf3345aea24ea4f38b4915921d8a" + "sha2": "7293c965570f02a590689e502fe2b0d94614a019" } ,{ "testCaseDescription": "javascript-array-delete-replacement-test", @@ -210,9 +210,9 @@ "filePaths": [ "array.js" ], - "sha1": "aac7a79ab7aecf3345aea24ea4f38b4915921d8a", + "sha1": "7293c965570f02a590689e502fe2b0d94614a019", "gitDir": "test/corpus/repos/javascript", - "sha2": "24c35a10f9dae3da5d9c331e50fe66b8be896736" + "sha2": "600a42656da1a28f6c013ab0e95a434f41f8d29c" } ,{ "testCaseDescription": "javascript-array-delete-test", @@ -243,9 +243,9 @@ "filePaths": [ "array.js" ], - "sha1": "24c35a10f9dae3da5d9c331e50fe66b8be896736", + "sha1": "600a42656da1a28f6c013ab0e95a434f41f8d29c", "gitDir": "test/corpus/repos/javascript", - "sha2": "84b4a8728ce89f0768b5ea0dcce540a133772e59" + "sha2": "a6243ff3c461e4c1a6602cfc302f425189e6d9c3" } ,{ "testCaseDescription": "javascript-array-delete-rest-test", @@ -276,7 +276,7 @@ "filePaths": [ "array.js" ], - "sha1": "84b4a8728ce89f0768b5ea0dcce540a133772e59", + "sha1": "a6243ff3c461e4c1a6602cfc302f425189e6d9c3", "gitDir": "test/corpus/repos/javascript", - "sha2": "7421caaeb3a46acf3fd36871e3fd56e4409df4c1" + "sha2": "0ee9c8e6c87189715a67160428ce11ee61012b05" }] diff --git a/test/corpus/diff-summaries/javascript/arrow-function.json b/test/corpus/diff-summaries/javascript/arrow-function.json index 5f854ba03..0922abf21 100644 --- a/test/corpus/diff-summaries/javascript/arrow-function.json +++ b/test/corpus/diff-summaries/javascript/arrow-function.json @@ -27,9 +27,9 @@ "filePaths": [ "arrow-function.js" ], - "sha1": "1331d4ffb544aebfa16c17c9c2ebbab19e6f422a", + "sha1": "292d11c2e4263aedc5c5b54a527d686428f8ddd1", "gitDir": "test/corpus/repos/javascript", - "sha2": "4d09b922ad63a1acd3b6afe3d68dd6dc22ba78c8" + "sha2": "6a7893d2e94099cd9fedb01b582e7ad4ff73e89d" } ,{ "testCaseDescription": "javascript-arrow-function-replacement-insert-test", @@ -77,9 +77,9 @@ "filePaths": [ "arrow-function.js" ], - "sha1": "4d09b922ad63a1acd3b6afe3d68dd6dc22ba78c8", + "sha1": "6a7893d2e94099cd9fedb01b582e7ad4ff73e89d", "gitDir": "test/corpus/repos/javascript", - "sha2": "6d4a9c5fe2f6ae81f03bf761385238d96409cd5c" + "sha2": "227e3fdb0b43676bfc752f04d14dc5c0c318f630" } ,{ "testCaseDescription": "javascript-arrow-function-delete-insert-test", @@ -123,9 +123,9 @@ "filePaths": [ "arrow-function.js" ], - "sha1": "6d4a9c5fe2f6ae81f03bf761385238d96409cd5c", + "sha1": "227e3fdb0b43676bfc752f04d14dc5c0c318f630", "gitDir": "test/corpus/repos/javascript", - "sha2": "955047d8cae03944863fe0457dab999410da00ee" + "sha2": "f093d99e79a285d5a41bb100fb86ff73e104d2fa" } ,{ "testCaseDescription": "javascript-arrow-function-replacement-test", @@ -169,9 +169,9 @@ "filePaths": [ "arrow-function.js" ], - "sha1": "955047d8cae03944863fe0457dab999410da00ee", + "sha1": "f093d99e79a285d5a41bb100fb86ff73e104d2fa", "gitDir": "test/corpus/repos/javascript", - "sha2": "4f886505083883d5ce313d51ae222b05044cb464" + "sha2": "dfa11dd0f9237b75f84ec26830f0159b15391da9" } ,{ "testCaseDescription": "javascript-arrow-function-delete-replacement-test", @@ -236,9 +236,9 @@ "filePaths": [ "arrow-function.js" ], - "sha1": "4f886505083883d5ce313d51ae222b05044cb464", + "sha1": "dfa11dd0f9237b75f84ec26830f0159b15391da9", "gitDir": "test/corpus/repos/javascript", - "sha2": "3f81a39022968106428052245cf475419ec283b6" + "sha2": "c0519b34f3408fc82a1f2baa7b7b48dbde82ead0" } ,{ "testCaseDescription": "javascript-arrow-function-delete-test", @@ -269,9 +269,9 @@ "filePaths": [ "arrow-function.js" ], - "sha1": "3f81a39022968106428052245cf475419ec283b6", + "sha1": "c0519b34f3408fc82a1f2baa7b7b48dbde82ead0", "gitDir": "test/corpus/repos/javascript", - "sha2": "d75e2c071c454713f7824114e29f4d99427c43f5" + "sha2": "e03369240a62811722d7d08730e3302d97c22f3f" } ,{ "testCaseDescription": "javascript-arrow-function-delete-rest-test", @@ -302,7 +302,7 @@ "filePaths": [ "arrow-function.js" ], - "sha1": "d75e2c071c454713f7824114e29f4d99427c43f5", + "sha1": "e03369240a62811722d7d08730e3302d97c22f3f", "gitDir": "test/corpus/repos/javascript", - "sha2": "4d63196a05b9443aebe166c10eaf31d60a162f7e" + "sha2": "ea881b604fbd6a7bff63837b413fbb2878da9525" }] diff --git a/test/corpus/diff-summaries/javascript/assignment.json b/test/corpus/diff-summaries/javascript/assignment.json index ceec1d68b..682b68aa2 100644 --- a/test/corpus/diff-summaries/javascript/assignment.json +++ b/test/corpus/diff-summaries/javascript/assignment.json @@ -27,9 +27,9 @@ "filePaths": [ "assignment.js" ], - "sha1": "1689419def381340a06222171173117f80ab169e", + "sha1": "031c53cff6b8f106847a7cd1da37a95d714890e3", "gitDir": "test/corpus/repos/javascript", - "sha2": "b5c863844f2f4c648119688662a2b85e597d6126" + "sha2": "daa8f9455f1a839218f42157fedd14a1f2c0b46e" } ,{ "testCaseDescription": "javascript-assignment-replacement-insert-test", @@ -77,9 +77,9 @@ "filePaths": [ "assignment.js" ], - "sha1": "b5c863844f2f4c648119688662a2b85e597d6126", + "sha1": "daa8f9455f1a839218f42157fedd14a1f2c0b46e", "gitDir": "test/corpus/repos/javascript", - "sha2": "a4a65b9fe496e319e6a5419bb406f3f6011e9e21" + "sha2": "ed425b43b199fcb3d66ac5d23b0b7dbe220ee22a" } ,{ "testCaseDescription": "javascript-assignment-delete-insert-test", @@ -123,9 +123,9 @@ "filePaths": [ "assignment.js" ], - "sha1": "a4a65b9fe496e319e6a5419bb406f3f6011e9e21", + "sha1": "ed425b43b199fcb3d66ac5d23b0b7dbe220ee22a", "gitDir": "test/corpus/repos/javascript", - "sha2": "aaf8ea43af02716f3eae9d8e2734aa6e59e212e2" + "sha2": "02875f86427d5e098f12a1f4cdde1b0dd659b29a" } ,{ "testCaseDescription": "javascript-assignment-replacement-test", @@ -169,9 +169,9 @@ "filePaths": [ "assignment.js" ], - "sha1": "aaf8ea43af02716f3eae9d8e2734aa6e59e212e2", + "sha1": "02875f86427d5e098f12a1f4cdde1b0dd659b29a", "gitDir": "test/corpus/repos/javascript", - "sha2": "85a5c7b18e7333cd721c165391f0a18df4b3bae1" + "sha2": "1f6bdc70edf556ba4e826ea6711f7064a3f81c45" } ,{ "testCaseDescription": "javascript-assignment-delete-replacement-test", @@ -236,9 +236,9 @@ "filePaths": [ "assignment.js" ], - "sha1": "85a5c7b18e7333cd721c165391f0a18df4b3bae1", + "sha1": "1f6bdc70edf556ba4e826ea6711f7064a3f81c45", "gitDir": "test/corpus/repos/javascript", - "sha2": "afc6f31261dda7281144aceaa36021e6aa5b019c" + "sha2": "58e91688ab485d4c9d359ab7a2007d718a9113d7" } ,{ "testCaseDescription": "javascript-assignment-delete-test", @@ -269,9 +269,9 @@ "filePaths": [ "assignment.js" ], - "sha1": "afc6f31261dda7281144aceaa36021e6aa5b019c", + "sha1": "58e91688ab485d4c9d359ab7a2007d718a9113d7", "gitDir": "test/corpus/repos/javascript", - "sha2": "a33ab633edb97c7a89d8e43129a98577769e5d15" + "sha2": "9c4967350cb94e3ccece24679e3b6f8695d7f5ee" } ,{ "testCaseDescription": "javascript-assignment-delete-rest-test", @@ -302,7 +302,7 @@ "filePaths": [ "assignment.js" ], - "sha1": "a33ab633edb97c7a89d8e43129a98577769e5d15", + "sha1": "9c4967350cb94e3ccece24679e3b6f8695d7f5ee", "gitDir": "test/corpus/repos/javascript", - "sha2": "6882106e2e1564145c50f664a6446f6c37b1ab3f" + "sha2": "a8610d7d0057162d3dbbb845175a0fc8d993e0d6" }] diff --git a/test/corpus/diff-summaries/javascript/bitwise-operator.json b/test/corpus/diff-summaries/javascript/bitwise-operator.json index bceddf51c..6c9511707 100644 --- a/test/corpus/diff-summaries/javascript/bitwise-operator.json +++ b/test/corpus/diff-summaries/javascript/bitwise-operator.json @@ -27,9 +27,9 @@ "filePaths": [ "bitwise-operator.js" ], - "sha1": "c77130c14c2dbfd795136ff0fd27924d67a13e12", + "sha1": "c9eeca7b41f404d72d81ffd3df9410d8c31ca047", "gitDir": "test/corpus/repos/javascript", - "sha2": "190cbea65dd6ddbe9827c35d43f4cb41a8fa8929" + "sha2": "4fc400a4eb7b1cfc1a100d9846e3710ff7c786bf" } ,{ "testCaseDescription": "javascript-bitwise-operator-replacement-insert-test", @@ -77,9 +77,9 @@ "filePaths": [ "bitwise-operator.js" ], - "sha1": "190cbea65dd6ddbe9827c35d43f4cb41a8fa8929", + "sha1": "4fc400a4eb7b1cfc1a100d9846e3710ff7c786bf", "gitDir": "test/corpus/repos/javascript", - "sha2": "f0fa4938e0e1070c42a732d4560110c87c29d66e" + "sha2": "35c56ac13d2b06f705d85436d59990ea5ca702cd" } ,{ "testCaseDescription": "javascript-bitwise-operator-delete-insert-test", @@ -123,9 +123,9 @@ "filePaths": [ "bitwise-operator.js" ], - "sha1": "f0fa4938e0e1070c42a732d4560110c87c29d66e", + "sha1": "35c56ac13d2b06f705d85436d59990ea5ca702cd", "gitDir": "test/corpus/repos/javascript", - "sha2": "1861e01a938f5df02b33bac4c8da59bbd208f8dc" + "sha2": "b6f9a8be0234a7634f488eee6a9fc74963f2c4cf" } ,{ "testCaseDescription": "javascript-bitwise-operator-replacement-test", @@ -169,9 +169,9 @@ "filePaths": [ "bitwise-operator.js" ], - "sha1": "1861e01a938f5df02b33bac4c8da59bbd208f8dc", + "sha1": "b6f9a8be0234a7634f488eee6a9fc74963f2c4cf", "gitDir": "test/corpus/repos/javascript", - "sha2": "4daaabf2eb29de89938a05544251cd3edc196c38" + "sha2": "21b29fd95f13d556e369f0eb1bdf250be26d228b" } ,{ "testCaseDescription": "javascript-bitwise-operator-delete-replacement-test", @@ -236,9 +236,9 @@ "filePaths": [ "bitwise-operator.js" ], - "sha1": "4daaabf2eb29de89938a05544251cd3edc196c38", + "sha1": "21b29fd95f13d556e369f0eb1bdf250be26d228b", "gitDir": "test/corpus/repos/javascript", - "sha2": "9e75dc90f18c35f845fbd0d9a398a4b02986b888" + "sha2": "8b40de098783b76e489b51b0635681e66c689563" } ,{ "testCaseDescription": "javascript-bitwise-operator-delete-test", @@ -269,9 +269,9 @@ "filePaths": [ "bitwise-operator.js" ], - "sha1": "9e75dc90f18c35f845fbd0d9a398a4b02986b888", + "sha1": "8b40de098783b76e489b51b0635681e66c689563", "gitDir": "test/corpus/repos/javascript", - "sha2": "dfd6ce59330ff71c41c66acf43df3e05ec594a1c" + "sha2": "69d13307ee856916150b04403772e70780df3f68" } ,{ "testCaseDescription": "javascript-bitwise-operator-delete-rest-test", @@ -302,7 +302,7 @@ "filePaths": [ "bitwise-operator.js" ], - "sha1": "dfd6ce59330ff71c41c66acf43df3e05ec594a1c", + "sha1": "69d13307ee856916150b04403772e70780df3f68", "gitDir": "test/corpus/repos/javascript", - "sha2": "4a348bc66ccc50e501fe3e49df1cd797d99ca405" + "sha2": "0d4682971dbf0345afd2593f1068dc25c4cd0e84" }] diff --git a/test/corpus/diff-summaries/javascript/boolean-operator.json b/test/corpus/diff-summaries/javascript/boolean-operator.json index c2eb82023..9cf313807 100644 --- a/test/corpus/diff-summaries/javascript/boolean-operator.json +++ b/test/corpus/diff-summaries/javascript/boolean-operator.json @@ -27,9 +27,9 @@ "filePaths": [ "boolean-operator.js" ], - "sha1": "cb37f95870629005756c374dade2599850dc09d3", + "sha1": "d8ca022a316c97349395e113ee5563dbfc64a120", "gitDir": "test/corpus/repos/javascript", - "sha2": "feae2d99618470e8d0a6cbe778297c6768e870a2" + "sha2": "8879f70952299b137792adc99277addb4dc9d8c2" } ,{ "testCaseDescription": "javascript-boolean-operator-replacement-insert-test", @@ -77,9 +77,9 @@ "filePaths": [ "boolean-operator.js" ], - "sha1": "feae2d99618470e8d0a6cbe778297c6768e870a2", + "sha1": "8879f70952299b137792adc99277addb4dc9d8c2", "gitDir": "test/corpus/repos/javascript", - "sha2": "0f357662936edfbdcc46648837258c42e48f4f91" + "sha2": "db4908a1194a49d60ddb8e6e58a6a2f208db63b7" } ,{ "testCaseDescription": "javascript-boolean-operator-delete-insert-test", @@ -90,9 +90,9 @@ "filePaths": [ "boolean-operator.js" ], - "sha1": "0f357662936edfbdcc46648837258c42e48f4f91", + "sha1": "db4908a1194a49d60ddb8e6e58a6a2f208db63b7", "gitDir": "test/corpus/repos/javascript", - "sha2": "426262cded94a831340aada02d1fd390b5be6370" + "sha2": "bcdb6b772f14dadda64d51dbf62acc0f8f8ba2b8" } ,{ "testCaseDescription": "javascript-boolean-operator-replacement-test", @@ -103,9 +103,9 @@ "filePaths": [ "boolean-operator.js" ], - "sha1": "426262cded94a831340aada02d1fd390b5be6370", + "sha1": "bcdb6b772f14dadda64d51dbf62acc0f8f8ba2b8", "gitDir": "test/corpus/repos/javascript", - "sha2": "851b05bfac7dadb37628481d50607d29d8cd6960" + "sha2": "ad89e401e551d28c64be54f8a25f60335e4f30cf" } ,{ "testCaseDescription": "javascript-boolean-operator-delete-replacement-test", @@ -136,9 +136,9 @@ "filePaths": [ "boolean-operator.js" ], - "sha1": "851b05bfac7dadb37628481d50607d29d8cd6960", + "sha1": "ad89e401e551d28c64be54f8a25f60335e4f30cf", "gitDir": "test/corpus/repos/javascript", - "sha2": "ae0501cdc7ef28e75317be147919ba8aea8dd12c" + "sha2": "24fea035ee6cc6549225dc7975fa95a95aa1602b" } ,{ "testCaseDescription": "javascript-boolean-operator-delete-test", @@ -169,9 +169,9 @@ "filePaths": [ "boolean-operator.js" ], - "sha1": "ae0501cdc7ef28e75317be147919ba8aea8dd12c", + "sha1": "24fea035ee6cc6549225dc7975fa95a95aa1602b", "gitDir": "test/corpus/repos/javascript", - "sha2": "0738acb204f7c855934c15c9aeec04d83f2ea892" + "sha2": "46299e80d6554a9d56ebe1c500e941627a5e6798" } ,{ "testCaseDescription": "javascript-boolean-operator-delete-rest-test", @@ -202,7 +202,7 @@ "filePaths": [ "boolean-operator.js" ], - "sha1": "0738acb204f7c855934c15c9aeec04d83f2ea892", + "sha1": "46299e80d6554a9d56ebe1c500e941627a5e6798", "gitDir": "test/corpus/repos/javascript", - "sha2": "c77130c14c2dbfd795136ff0fd27924d67a13e12" + "sha2": "c9eeca7b41f404d72d81ffd3df9410d8c31ca047" }] diff --git a/test/corpus/diff-summaries/javascript/chained-callbacks.json b/test/corpus/diff-summaries/javascript/chained-callbacks.json index 7373441f2..4a035d49e 100644 --- a/test/corpus/diff-summaries/javascript/chained-callbacks.json +++ b/test/corpus/diff-summaries/javascript/chained-callbacks.json @@ -27,9 +27,9 @@ "filePaths": [ "chained-callbacks.js" ], - "sha1": "26f941c6191463416b1c6a56314b19dfe5d09221", + "sha1": "a8e5ca2f57c1c13f0d18a94196e0cafb7cbc2c39", "gitDir": "test/corpus/repos/javascript", - "sha2": "1feed1cf1d95ca3dd414517b6209f4b939f9a424" + "sha2": "34242f9f044c914ae73dc24605730efb2dee3cdc" } ,{ "testCaseDescription": "javascript-chained-callbacks-replacement-insert-test", @@ -77,9 +77,9 @@ "filePaths": [ "chained-callbacks.js" ], - "sha1": "1feed1cf1d95ca3dd414517b6209f4b939f9a424", + "sha1": "34242f9f044c914ae73dc24605730efb2dee3cdc", "gitDir": "test/corpus/repos/javascript", - "sha2": "07ee33b6378c5521565478ca27a988226db043bc" + "sha2": "e184d436519216be917d2238ff36e28ef57aa462" } ,{ "testCaseDescription": "javascript-chained-callbacks-delete-insert-test", @@ -183,9 +183,9 @@ "filePaths": [ "chained-callbacks.js" ], - "sha1": "07ee33b6378c5521565478ca27a988226db043bc", + "sha1": "e184d436519216be917d2238ff36e28ef57aa462", "gitDir": "test/corpus/repos/javascript", - "sha2": "cde3100134b868aee4b00d1f76df2be1acced6d0" + "sha2": "d43987311e8c43612449d11670c9edab65f935e5" } ,{ "testCaseDescription": "javascript-chained-callbacks-replacement-test", @@ -289,9 +289,9 @@ "filePaths": [ "chained-callbacks.js" ], - "sha1": "cde3100134b868aee4b00d1f76df2be1acced6d0", + "sha1": "d43987311e8c43612449d11670c9edab65f935e5", "gitDir": "test/corpus/repos/javascript", - "sha2": "6442a64e98e7f30d16e22ee22bcf2586b4cf03a4" + "sha2": "2512d2e3685d8121ce3a83482ccd6f0e62211ba6" } ,{ "testCaseDescription": "javascript-chained-callbacks-delete-replacement-test", @@ -356,9 +356,9 @@ "filePaths": [ "chained-callbacks.js" ], - "sha1": "6442a64e98e7f30d16e22ee22bcf2586b4cf03a4", + "sha1": "2512d2e3685d8121ce3a83482ccd6f0e62211ba6", "gitDir": "test/corpus/repos/javascript", - "sha2": "3bcdf485f97763d63d4c0031d2f780c1a17c014f" + "sha2": "9588d6d52f5beaf2f6d2f7191713872815b69d94" } ,{ "testCaseDescription": "javascript-chained-callbacks-delete-test", @@ -389,9 +389,9 @@ "filePaths": [ "chained-callbacks.js" ], - "sha1": "3bcdf485f97763d63d4c0031d2f780c1a17c014f", + "sha1": "9588d6d52f5beaf2f6d2f7191713872815b69d94", "gitDir": "test/corpus/repos/javascript", - "sha2": "77aa8df2f2a53b78df109832b331ac606d4eaa30" + "sha2": "269c6e87ad867ae1efcf0c64e487e506299e5c54" } ,{ "testCaseDescription": "javascript-chained-callbacks-delete-rest-test", @@ -422,7 +422,7 @@ "filePaths": [ "chained-callbacks.js" ], - "sha1": "77aa8df2f2a53b78df109832b331ac606d4eaa30", + "sha1": "269c6e87ad867ae1efcf0c64e487e506299e5c54", "gitDir": "test/corpus/repos/javascript", - "sha2": "66f76d6c6d3a517f3f4c016d8e03d3497cf724c6" + "sha2": "adef6baf8b5eef8703844039dc7001ac32c9ce46" }] diff --git a/test/corpus/diff-summaries/javascript/chained-property-access.json b/test/corpus/diff-summaries/javascript/chained-property-access.json index d237f9f96..6fc8fcb33 100644 --- a/test/corpus/diff-summaries/javascript/chained-property-access.json +++ b/test/corpus/diff-summaries/javascript/chained-property-access.json @@ -27,9 +27,9 @@ "filePaths": [ "chained-property-access.js" ], - "sha1": "5172568a010252e98966d57a1c3fc1ade326f9ab", + "sha1": "6d2a9f7093c2227f7d7eeedabf694118f5f17c73", "gitDir": "test/corpus/repos/javascript", - "sha2": "f59315119ff60b7a5eec00c298a3dbaced0b59d4" + "sha2": "6180716e37d5a804f5a457db154e6a10f0ca3e79" } ,{ "testCaseDescription": "javascript-chained-property-access-replacement-insert-test", @@ -77,9 +77,9 @@ "filePaths": [ "chained-property-access.js" ], - "sha1": "f59315119ff60b7a5eec00c298a3dbaced0b59d4", + "sha1": "6180716e37d5a804f5a457db154e6a10f0ca3e79", "gitDir": "test/corpus/repos/javascript", - "sha2": "8bda63987dd989d6e42ddc5661fe2b22bb0cec77" + "sha2": "374c46575fecedbe061db087d3705eb484b2421d" } ,{ "testCaseDescription": "javascript-chained-property-access-delete-insert-test", @@ -153,9 +153,9 @@ "filePaths": [ "chained-property-access.js" ], - "sha1": "8bda63987dd989d6e42ddc5661fe2b22bb0cec77", + "sha1": "374c46575fecedbe061db087d3705eb484b2421d", "gitDir": "test/corpus/repos/javascript", - "sha2": "49366eb9b5adfc0372d1b58a87acd15c8052a606" + "sha2": "85b45ee758c2258e476e829548c7e37f53487548" } ,{ "testCaseDescription": "javascript-chained-property-access-replacement-test", @@ -229,9 +229,9 @@ "filePaths": [ "chained-property-access.js" ], - "sha1": "49366eb9b5adfc0372d1b58a87acd15c8052a606", + "sha1": "85b45ee758c2258e476e829548c7e37f53487548", "gitDir": "test/corpus/repos/javascript", - "sha2": "301c255bc3e410697be6bb102e8b9e9d107666a0" + "sha2": "bd643c48bcf421ba799eeeefd97935683be59576" } ,{ "testCaseDescription": "javascript-chained-property-access-delete-replacement-test", @@ -296,9 +296,9 @@ "filePaths": [ "chained-property-access.js" ], - "sha1": "301c255bc3e410697be6bb102e8b9e9d107666a0", + "sha1": "bd643c48bcf421ba799eeeefd97935683be59576", "gitDir": "test/corpus/repos/javascript", - "sha2": "49ea61cc98251e249f226f8787bbee08511fe9e9" + "sha2": "d2ed72cd988fc73a9658725e3e2abd2a5da1d9c2" } ,{ "testCaseDescription": "javascript-chained-property-access-delete-test", @@ -329,9 +329,9 @@ "filePaths": [ "chained-property-access.js" ], - "sha1": "49ea61cc98251e249f226f8787bbee08511fe9e9", + "sha1": "d2ed72cd988fc73a9658725e3e2abd2a5da1d9c2", "gitDir": "test/corpus/repos/javascript", - "sha2": "8b1e3d552a64cdd2e542affda6527af005ebcb45" + "sha2": "fcf5600c10a36f83f8eb92b778c651e4cd5e4347" } ,{ "testCaseDescription": "javascript-chained-property-access-delete-rest-test", @@ -362,7 +362,7 @@ "filePaths": [ "chained-property-access.js" ], - "sha1": "8b1e3d552a64cdd2e542affda6527af005ebcb45", + "sha1": "fcf5600c10a36f83f8eb92b778c651e4cd5e4347", "gitDir": "test/corpus/repos/javascript", - "sha2": "26f941c6191463416b1c6a56314b19dfe5d09221" + "sha2": "a8e5ca2f57c1c13f0d18a94196e0cafb7cbc2c39" }] diff --git a/test/corpus/diff-summaries/javascript/class.json b/test/corpus/diff-summaries/javascript/class.json index 5adc5f1a1..c5679f3c8 100644 --- a/test/corpus/diff-summaries/javascript/class.json +++ b/test/corpus/diff-summaries/javascript/class.json @@ -27,9 +27,9 @@ "filePaths": [ "class.js" ], - "sha1": "3c4c5929ba3cb9bc23b211787745791de8774d2d", + "sha1": "83627007e919d5e812d83d6d96953a00e81369c0", "gitDir": "test/corpus/repos/javascript", - "sha2": "b728e40d8d1a035c46c62d3edc01f1e30d06bf59" + "sha2": "d767c58b76e3cbfe7f864b591ca6c84e8f6e2927" } ,{ "testCaseDescription": "javascript-class-replacement-insert-test", @@ -77,9 +77,9 @@ "filePaths": [ "class.js" ], - "sha1": "b728e40d8d1a035c46c62d3edc01f1e30d06bf59", + "sha1": "d767c58b76e3cbfe7f864b591ca6c84e8f6e2927", "gitDir": "test/corpus/repos/javascript", - "sha2": "e4a75438dfa8e247778fa6e8319ccc35fa9cdcb3" + "sha2": "a651a0b93739f2b5e8386dfd512b74ddffe3a18a" } ,{ "testCaseDescription": "javascript-class-delete-insert-test", @@ -183,9 +183,9 @@ "filePaths": [ "class.js" ], - "sha1": "e4a75438dfa8e247778fa6e8319ccc35fa9cdcb3", + "sha1": "a651a0b93739f2b5e8386dfd512b74ddffe3a18a", "gitDir": "test/corpus/repos/javascript", - "sha2": "a2cd250b0659258473156b0ad3bad3d081b8f047" + "sha2": "041316ee304f230e5fa4ef596e509cb0fd40eb1f" } ,{ "testCaseDescription": "javascript-class-replacement-test", @@ -289,9 +289,9 @@ "filePaths": [ "class.js" ], - "sha1": "a2cd250b0659258473156b0ad3bad3d081b8f047", + "sha1": "041316ee304f230e5fa4ef596e509cb0fd40eb1f", "gitDir": "test/corpus/repos/javascript", - "sha2": "0558a17e26ea263027bc60b26ca6f9b40c923746" + "sha2": "72ad8365d1dd791d49623878ff63f6efc63ee3e5" } ,{ "testCaseDescription": "javascript-class-delete-replacement-test", @@ -356,9 +356,9 @@ "filePaths": [ "class.js" ], - "sha1": "0558a17e26ea263027bc60b26ca6f9b40c923746", + "sha1": "72ad8365d1dd791d49623878ff63f6efc63ee3e5", "gitDir": "test/corpus/repos/javascript", - "sha2": "4247bf279aca71be7ae67e8853a46e56ecc1bcdc" + "sha2": "fa5b9e801beb4242d38b1fcbf3180997d5cd141c" } ,{ "testCaseDescription": "javascript-class-delete-test", @@ -389,9 +389,9 @@ "filePaths": [ "class.js" ], - "sha1": "4247bf279aca71be7ae67e8853a46e56ecc1bcdc", + "sha1": "fa5b9e801beb4242d38b1fcbf3180997d5cd141c", "gitDir": "test/corpus/repos/javascript", - "sha2": "8724757eda59b1c3a89ac88298c706023d3480e5" + "sha2": "4d718b604febd5b0e89d62f2c32401aea6db9e94" } ,{ "testCaseDescription": "javascript-class-delete-rest-test", @@ -422,7 +422,7 @@ "filePaths": [ "class.js" ], - "sha1": "8724757eda59b1c3a89ac88298c706023d3480e5", + "sha1": "4d718b604febd5b0e89d62f2c32401aea6db9e94", "gitDir": "test/corpus/repos/javascript", - "sha2": "6c3b6d5c7d426a657e90d97cdfd248b2453bc087" + "sha2": "407eb0654feb336967cfa7e099e277590d97ea6d" }] diff --git a/test/corpus/diff-summaries/javascript/comma-operator.json b/test/corpus/diff-summaries/javascript/comma-operator.json index 3797a9341..afd3f1d90 100644 --- a/test/corpus/diff-summaries/javascript/comma-operator.json +++ b/test/corpus/diff-summaries/javascript/comma-operator.json @@ -44,9 +44,9 @@ "filePaths": [ "comma-operator.js" ], - "sha1": "25e371a5c0ef7434f562af7ca9a9bfab5a157932", + "sha1": "1cda03e29bc707037e0b55c899bc9d9fec1239db", "gitDir": "test/corpus/repos/javascript", - "sha2": "1c93fcbaca04d643a2ddeabe0b6e5d322df2a4fb" + "sha2": "920808e907dca825300353988c74581c5ecda2ef" } ,{ "testCaseDescription": "javascript-comma-operator-replacement-insert-test", @@ -111,9 +111,9 @@ "filePaths": [ "comma-operator.js" ], - "sha1": "1c93fcbaca04d643a2ddeabe0b6e5d322df2a4fb", + "sha1": "920808e907dca825300353988c74581c5ecda2ef", "gitDir": "test/corpus/repos/javascript", - "sha2": "331db399698c11dfc5b4ff49f72b77e3910d5f01" + "sha2": "d3a5a9b3abd6447ccef0b274d3eb2578a33a31a7" } ,{ "testCaseDescription": "javascript-comma-operator-delete-insert-test", @@ -178,9 +178,9 @@ "filePaths": [ "comma-operator.js" ], - "sha1": "331db399698c11dfc5b4ff49f72b77e3910d5f01", + "sha1": "d3a5a9b3abd6447ccef0b274d3eb2578a33a31a7", "gitDir": "test/corpus/repos/javascript", - "sha2": "d82e3a6dffefade301dbda072bf59931587b9196" + "sha2": "5596ae83228451e6923a17ab6c04643cd6cec60e" } ,{ "testCaseDescription": "javascript-comma-operator-replacement-test", @@ -245,9 +245,9 @@ "filePaths": [ "comma-operator.js" ], - "sha1": "d82e3a6dffefade301dbda072bf59931587b9196", + "sha1": "5596ae83228451e6923a17ab6c04643cd6cec60e", "gitDir": "test/corpus/repos/javascript", - "sha2": "bcb931f34cdfe5d7f167afd79d1d1196284f9587" + "sha2": "abffc326e31c8e683d638e33541c98e6a3a2d45b" } ,{ "testCaseDescription": "javascript-comma-operator-delete-replacement-test", @@ -329,9 +329,9 @@ "filePaths": [ "comma-operator.js" ], - "sha1": "bcb931f34cdfe5d7f167afd79d1d1196284f9587", + "sha1": "abffc326e31c8e683d638e33541c98e6a3a2d45b", "gitDir": "test/corpus/repos/javascript", - "sha2": "59f0b3ae2045827b2be7200f3ae10d13daef566e" + "sha2": "a5e093ceccbeb8a3a19bc72aa15bdc8bd228a291" } ,{ "testCaseDescription": "javascript-comma-operator-delete-test", @@ -379,9 +379,9 @@ "filePaths": [ "comma-operator.js" ], - "sha1": "59f0b3ae2045827b2be7200f3ae10d13daef566e", + "sha1": "a5e093ceccbeb8a3a19bc72aa15bdc8bd228a291", "gitDir": "test/corpus/repos/javascript", - "sha2": "8f59d35152aa46577234e3fd8c00122b9182574d" + "sha2": "4ceb6b816b56136ad1ee95bddf17552371937425" } ,{ "testCaseDescription": "javascript-comma-operator-delete-rest-test", @@ -412,7 +412,7 @@ "filePaths": [ "comma-operator.js" ], - "sha1": "8f59d35152aa46577234e3fd8c00122b9182574d", + "sha1": "4ceb6b816b56136ad1ee95bddf17552371937425", "gitDir": "test/corpus/repos/javascript", - "sha2": "7086396295d14f41207e8fbae4d350f2672a77dd" + "sha2": "216c9ba07743064780c37d5f07af95a9dee2bf96" }] diff --git a/test/corpus/diff-summaries/javascript/comment.json b/test/corpus/diff-summaries/javascript/comment.json index 2c147d961..00ca1e6aa 100644 --- a/test/corpus/diff-summaries/javascript/comment.json +++ b/test/corpus/diff-summaries/javascript/comment.json @@ -27,9 +27,9 @@ "filePaths": [ "comment.js" ], - "sha1": "a67c36dee6afa77efd8005ab23227f683239d35e", + "sha1": "72fe137f23a68d773c76719f790807ead00ef84a", "gitDir": "test/corpus/repos/javascript", - "sha2": "7d283c6fbe1d5b29e2ab629ee8d18e668b206e80" + "sha2": "e5586684ed84dd036c71083544925f5230281b6f" } ,{ "testCaseDescription": "javascript-comment-replacement-insert-test", @@ -77,9 +77,9 @@ "filePaths": [ "comment.js" ], - "sha1": "7d283c6fbe1d5b29e2ab629ee8d18e668b206e80", + "sha1": "e5586684ed84dd036c71083544925f5230281b6f", "gitDir": "test/corpus/repos/javascript", - "sha2": "7368c3a098046a807d136e1e86467f6c2b6ec81a" + "sha2": "7555438a387aedf7944f925ea199c6feec2ddf69" } ,{ "testCaseDescription": "javascript-comment-delete-insert-test", @@ -123,9 +123,9 @@ "filePaths": [ "comment.js" ], - "sha1": "7368c3a098046a807d136e1e86467f6c2b6ec81a", + "sha1": "7555438a387aedf7944f925ea199c6feec2ddf69", "gitDir": "test/corpus/repos/javascript", - "sha2": "1cf6f98c7f88af7a9a75863c4fd38202308014ea" + "sha2": "e6271149f264d81f8cf188641f7f75b36ba477f9" } ,{ "testCaseDescription": "javascript-comment-replacement-test", @@ -169,9 +169,9 @@ "filePaths": [ "comment.js" ], - "sha1": "1cf6f98c7f88af7a9a75863c4fd38202308014ea", + "sha1": "e6271149f264d81f8cf188641f7f75b36ba477f9", "gitDir": "test/corpus/repos/javascript", - "sha2": "aafd41680947235874cd0070f3970a712f140f79" + "sha2": "103e537a1240bdeaeb6b28663f43daacbd1cd824" } ,{ "testCaseDescription": "javascript-comment-delete-replacement-test", @@ -236,9 +236,9 @@ "filePaths": [ "comment.js" ], - "sha1": "aafd41680947235874cd0070f3970a712f140f79", + "sha1": "103e537a1240bdeaeb6b28663f43daacbd1cd824", "gitDir": "test/corpus/repos/javascript", - "sha2": "6b6457fbd3a6977f7041f32f5cbb59d86f82853a" + "sha2": "073a2a8ff5f61ca471f2b8152207301fb0583d3c" } ,{ "testCaseDescription": "javascript-comment-delete-test", @@ -269,9 +269,9 @@ "filePaths": [ "comment.js" ], - "sha1": "6b6457fbd3a6977f7041f32f5cbb59d86f82853a", + "sha1": "073a2a8ff5f61ca471f2b8152207301fb0583d3c", "gitDir": "test/corpus/repos/javascript", - "sha2": "1f1632420d5cb8f7794652942c29badb4b2ea481" + "sha2": "cac56c3383233f34fe16d2427d319aac5f4ef1e8" } ,{ "testCaseDescription": "javascript-comment-delete-rest-test", @@ -302,7 +302,7 @@ "filePaths": [ "comment.js" ], - "sha1": "1f1632420d5cb8f7794652942c29badb4b2ea481", + "sha1": "cac56c3383233f34fe16d2427d319aac5f4ef1e8", "gitDir": "test/corpus/repos/javascript", - "sha2": "9edcc470495aad2ae2b395a18179ec07829ad591" + "sha2": "ebc2ca02f6b0c4744e33e2d191158cc7f2b19a60" }] diff --git a/test/corpus/diff-summaries/javascript/constructor-call.json b/test/corpus/diff-summaries/javascript/constructor-call.json index abc18dedb..1e7825b8f 100644 --- a/test/corpus/diff-summaries/javascript/constructor-call.json +++ b/test/corpus/diff-summaries/javascript/constructor-call.json @@ -27,9 +27,9 @@ "filePaths": [ "constructor-call.js" ], - "sha1": "e67227e82c01378ae1102d7579e52a47e06ef16a", + "sha1": "143f944ead8b453c8d4f2a24f35b6e64406217ff", "gitDir": "test/corpus/repos/javascript", - "sha2": "86912d55ecac17b3ce2c8370e06b361daa72a63d" + "sha2": "b3866e0ac05a545a76032b23956be2d3b5696048" } ,{ "testCaseDescription": "javascript-constructor-call-replacement-insert-test", @@ -77,9 +77,9 @@ "filePaths": [ "constructor-call.js" ], - "sha1": "86912d55ecac17b3ce2c8370e06b361daa72a63d", + "sha1": "b3866e0ac05a545a76032b23956be2d3b5696048", "gitDir": "test/corpus/repos/javascript", - "sha2": "eec1530d637fa82ada4aaf549e576f8f4530b458" + "sha2": "70242b1d9ffec4b1fb5115d2d3885e6b1e6bb0ae" } ,{ "testCaseDescription": "javascript-constructor-call-delete-insert-test", @@ -123,9 +123,9 @@ "filePaths": [ "constructor-call.js" ], - "sha1": "eec1530d637fa82ada4aaf549e576f8f4530b458", + "sha1": "70242b1d9ffec4b1fb5115d2d3885e6b1e6bb0ae", "gitDir": "test/corpus/repos/javascript", - "sha2": "6823bb31a08af05908b3276127c191d5bdfd89b6" + "sha2": "c4c78ad8c80317bea2ec53f28821e4af48c0bd88" } ,{ "testCaseDescription": "javascript-constructor-call-replacement-test", @@ -169,9 +169,9 @@ "filePaths": [ "constructor-call.js" ], - "sha1": "6823bb31a08af05908b3276127c191d5bdfd89b6", + "sha1": "c4c78ad8c80317bea2ec53f28821e4af48c0bd88", "gitDir": "test/corpus/repos/javascript", - "sha2": "0d42b2f3722e4f1bd33f10099a2b9b92368ea62e" + "sha2": "1f1239540c4737ef3f6a04878602bd5a8148e645" } ,{ "testCaseDescription": "javascript-constructor-call-delete-replacement-test", @@ -236,9 +236,9 @@ "filePaths": [ "constructor-call.js" ], - "sha1": "0d42b2f3722e4f1bd33f10099a2b9b92368ea62e", + "sha1": "1f1239540c4737ef3f6a04878602bd5a8148e645", "gitDir": "test/corpus/repos/javascript", - "sha2": "b17ad17aa14e02fd6c5a6593e7c9e1b6be2ace5d" + "sha2": "2884df62a12b83d784761b5cce876be58939a5c5" } ,{ "testCaseDescription": "javascript-constructor-call-delete-test", @@ -269,9 +269,9 @@ "filePaths": [ "constructor-call.js" ], - "sha1": "b17ad17aa14e02fd6c5a6593e7c9e1b6be2ace5d", + "sha1": "2884df62a12b83d784761b5cce876be58939a5c5", "gitDir": "test/corpus/repos/javascript", - "sha2": "c228196872cbf218531b4e3bd82250e2bce507da" + "sha2": "0151a1ccd7bd4e96dbf6ab51cbb8ef5259f9d58d" } ,{ "testCaseDescription": "javascript-constructor-call-delete-rest-test", @@ -302,7 +302,7 @@ "filePaths": [ "constructor-call.js" ], - "sha1": "c228196872cbf218531b4e3bd82250e2bce507da", + "sha1": "0151a1ccd7bd4e96dbf6ab51cbb8ef5259f9d58d", "gitDir": "test/corpus/repos/javascript", - "sha2": "31ae73e147d1cd8cf95cfdf871344f18fdc91fa2" + "sha2": "29d3dd029a42aa320f2d154af468cc33e9fc7be2" }] diff --git a/test/corpus/diff-summaries/javascript/delete-operator.json b/test/corpus/diff-summaries/javascript/delete-operator.json index c20d2f6be..86467c2ae 100644 --- a/test/corpus/diff-summaries/javascript/delete-operator.json +++ b/test/corpus/diff-summaries/javascript/delete-operator.json @@ -27,9 +27,9 @@ "filePaths": [ "delete-operator.js" ], - "sha1": "c012557afb55395556a9209537f977c480c9cfa2", + "sha1": "215414e0397973e2f7d49a8edff9cf1d84fad02a", "gitDir": "test/corpus/repos/javascript", - "sha2": "6b1159e64aeea120283214debcf6b90846dd2d25" + "sha2": "d8c710fa6ec1bc818d5abd0e03a3396c962cbf09" } ,{ "testCaseDescription": "javascript-delete-operator-replacement-insert-test", @@ -77,9 +77,9 @@ "filePaths": [ "delete-operator.js" ], - "sha1": "6b1159e64aeea120283214debcf6b90846dd2d25", + "sha1": "d8c710fa6ec1bc818d5abd0e03a3396c962cbf09", "gitDir": "test/corpus/repos/javascript", - "sha2": "30def9e5c20b4b581b85c5fa83ce538254f9cf92" + "sha2": "ea533b83665a30a88932b4eeb27cb010d5da3e62" } ,{ "testCaseDescription": "javascript-delete-operator-delete-insert-test", @@ -123,9 +123,9 @@ "filePaths": [ "delete-operator.js" ], - "sha1": "30def9e5c20b4b581b85c5fa83ce538254f9cf92", + "sha1": "ea533b83665a30a88932b4eeb27cb010d5da3e62", "gitDir": "test/corpus/repos/javascript", - "sha2": "f5f742849965b8ac6d6ddac053ae7ad8638d3f56" + "sha2": "76af60d9b2739cd60803165c951a06f1f43b28d6" } ,{ "testCaseDescription": "javascript-delete-operator-replacement-test", @@ -169,9 +169,9 @@ "filePaths": [ "delete-operator.js" ], - "sha1": "f5f742849965b8ac6d6ddac053ae7ad8638d3f56", + "sha1": "76af60d9b2739cd60803165c951a06f1f43b28d6", "gitDir": "test/corpus/repos/javascript", - "sha2": "28436cc38cd7b95a4f00bb6764bb77f5d7ae3e63" + "sha2": "c5d56aba0a3f9250ea6694fb8b69e665e108fcff" } ,{ "testCaseDescription": "javascript-delete-operator-delete-replacement-test", @@ -236,9 +236,9 @@ "filePaths": [ "delete-operator.js" ], - "sha1": "28436cc38cd7b95a4f00bb6764bb77f5d7ae3e63", + "sha1": "c5d56aba0a3f9250ea6694fb8b69e665e108fcff", "gitDir": "test/corpus/repos/javascript", - "sha2": "24b9fc05822bbc3b202fbe797de7daab301bf045" + "sha2": "f84b7f615724f057da0b037ba8942ca64baca215" } ,{ "testCaseDescription": "javascript-delete-operator-delete-test", @@ -269,9 +269,9 @@ "filePaths": [ "delete-operator.js" ], - "sha1": "24b9fc05822bbc3b202fbe797de7daab301bf045", + "sha1": "f84b7f615724f057da0b037ba8942ca64baca215", "gitDir": "test/corpus/repos/javascript", - "sha2": "16b0f30eb7f79f324a914ab14940e3ebb1e0f376" + "sha2": "f5ecaefd1ea1a6aab1fe3b87edade118bc047069" } ,{ "testCaseDescription": "javascript-delete-operator-delete-rest-test", @@ -302,7 +302,7 @@ "filePaths": [ "delete-operator.js" ], - "sha1": "16b0f30eb7f79f324a914ab14940e3ebb1e0f376", + "sha1": "f5ecaefd1ea1a6aab1fe3b87edade118bc047069", "gitDir": "test/corpus/repos/javascript", - "sha2": "4c9359461db3f23921b2af834190b8c9966fa455" + "sha2": "9dd33ff948d47044417ab8a6cb2dd82903a8a1b4" }] diff --git a/test/corpus/diff-summaries/javascript/do-while-statement.json b/test/corpus/diff-summaries/javascript/do-while-statement.json index 077225210..cebbb0a7e 100644 --- a/test/corpus/diff-summaries/javascript/do-while-statement.json +++ b/test/corpus/diff-summaries/javascript/do-while-statement.json @@ -27,9 +27,9 @@ "filePaths": [ "do-while-statement.js" ], - "sha1": "2991c8cdbe1144d3164c0fc0075cb5388e06583b", + "sha1": "b9bce32850180705594c7350911bd0714243f188", "gitDir": "test/corpus/repos/javascript", - "sha2": "fc1fd9e059e6088b851598dc684d5408adbf0168" + "sha2": "feb124cab094dde09b565be6f2996a9718b336a1" } ,{ "testCaseDescription": "javascript-do-while-statement-replacement-insert-test", @@ -77,9 +77,9 @@ "filePaths": [ "do-while-statement.js" ], - "sha1": "fc1fd9e059e6088b851598dc684d5408adbf0168", + "sha1": "feb124cab094dde09b565be6f2996a9718b336a1", "gitDir": "test/corpus/repos/javascript", - "sha2": "324526a23b5490a9859a781516afa5e58a66d774" + "sha2": "67aa4101b8d9063a8392ac374f99552ced02dcf5" } ,{ "testCaseDescription": "javascript-do-while-statement-delete-insert-test", @@ -153,9 +153,9 @@ "filePaths": [ "do-while-statement.js" ], - "sha1": "324526a23b5490a9859a781516afa5e58a66d774", + "sha1": "67aa4101b8d9063a8392ac374f99552ced02dcf5", "gitDir": "test/corpus/repos/javascript", - "sha2": "6163229e116d6f51f04f0865b21705630e6e4329" + "sha2": "47f65b68c178b04fb6235d9ace27cd4be21f882c" } ,{ "testCaseDescription": "javascript-do-while-statement-replacement-test", @@ -229,9 +229,9 @@ "filePaths": [ "do-while-statement.js" ], - "sha1": "6163229e116d6f51f04f0865b21705630e6e4329", + "sha1": "47f65b68c178b04fb6235d9ace27cd4be21f882c", "gitDir": "test/corpus/repos/javascript", - "sha2": "6cfc9a2d6fdbcd14d80a9519e5c9e3d66092950e" + "sha2": "21bd4c94aeec230846083136748043dff480d670" } ,{ "testCaseDescription": "javascript-do-while-statement-delete-replacement-test", @@ -296,9 +296,9 @@ "filePaths": [ "do-while-statement.js" ], - "sha1": "6cfc9a2d6fdbcd14d80a9519e5c9e3d66092950e", + "sha1": "21bd4c94aeec230846083136748043dff480d670", "gitDir": "test/corpus/repos/javascript", - "sha2": "9b5e3c1beb3f77b171aa0d6fcf01af966d96978a" + "sha2": "8c37de8d14d78dac20ddb465749f7c48e0127f1f" } ,{ "testCaseDescription": "javascript-do-while-statement-delete-test", @@ -329,9 +329,9 @@ "filePaths": [ "do-while-statement.js" ], - "sha1": "9b5e3c1beb3f77b171aa0d6fcf01af966d96978a", + "sha1": "8c37de8d14d78dac20ddb465749f7c48e0127f1f", "gitDir": "test/corpus/repos/javascript", - "sha2": "b4a3e1ab3c7306658c103f007c53334d8b27783c" + "sha2": "b49364de77f4824a01f67f3e988806f0ad800219" } ,{ "testCaseDescription": "javascript-do-while-statement-delete-rest-test", @@ -362,7 +362,7 @@ "filePaths": [ "do-while-statement.js" ], - "sha1": "b4a3e1ab3c7306658c103f007c53334d8b27783c", + "sha1": "b49364de77f4824a01f67f3e988806f0ad800219", "gitDir": "test/corpus/repos/javascript", - "sha2": "11ce49dc14d6c3b4c0baef54a2456d4bc667b992" + "sha2": "ea1cb608a188b06972bcdf47db341f8b953076b1" }] diff --git a/test/corpus/diff-summaries/javascript/false.json b/test/corpus/diff-summaries/javascript/false.json index 4ef6357b4..79ccd0369 100644 --- a/test/corpus/diff-summaries/javascript/false.json +++ b/test/corpus/diff-summaries/javascript/false.json @@ -27,9 +27,9 @@ "filePaths": [ "false.js" ], - "sha1": "9c5eadaa5e35756fff0d96ba9830a7e0dbf30fd7", + "sha1": "2729ff0e359b38bda1f650d3283d4116dc2fa3ad", "gitDir": "test/corpus/repos/javascript", - "sha2": "9d32877cdcecf69747e88be24da7b721a64d27ac" + "sha2": "f3388f96624945060a50d25605d1391e28d228c8" } ,{ "testCaseDescription": "javascript-false-replacement-insert-test", @@ -77,9 +77,9 @@ "filePaths": [ "false.js" ], - "sha1": "9d32877cdcecf69747e88be24da7b721a64d27ac", + "sha1": "f3388f96624945060a50d25605d1391e28d228c8", "gitDir": "test/corpus/repos/javascript", - "sha2": "4e71c4594699213f53e0b4a77b2623b6f8494ace" + "sha2": "db41deeb70100e3865202cc00e8e58aee3872cc6" } ,{ "testCaseDescription": "javascript-false-delete-insert-test", @@ -127,9 +127,9 @@ "filePaths": [ "false.js" ], - "sha1": "4e71c4594699213f53e0b4a77b2623b6f8494ace", + "sha1": "db41deeb70100e3865202cc00e8e58aee3872cc6", "gitDir": "test/corpus/repos/javascript", - "sha2": "b048ef1312ed02ee53c84180a16525a67ad70242" + "sha2": "007e522abd031d402ea364bbe7fa4794512b8831" } ,{ "testCaseDescription": "javascript-false-replacement-test", @@ -177,9 +177,9 @@ "filePaths": [ "false.js" ], - "sha1": "b048ef1312ed02ee53c84180a16525a67ad70242", + "sha1": "007e522abd031d402ea364bbe7fa4794512b8831", "gitDir": "test/corpus/repos/javascript", - "sha2": "15d1111d0020c65e3fca9491cb735534fb26e5a9" + "sha2": "7e20e8bcefefbd5d330dff0036879a5d61b20eaa" } ,{ "testCaseDescription": "javascript-false-delete-replacement-test", @@ -244,9 +244,9 @@ "filePaths": [ "false.js" ], - "sha1": "15d1111d0020c65e3fca9491cb735534fb26e5a9", + "sha1": "7e20e8bcefefbd5d330dff0036879a5d61b20eaa", "gitDir": "test/corpus/repos/javascript", - "sha2": "15884b8d34208b933c4319248220797995363a4c" + "sha2": "b4998a49cb6282b601fe5a1c784f1f7a01353d95" } ,{ "testCaseDescription": "javascript-false-delete-test", @@ -277,9 +277,9 @@ "filePaths": [ "false.js" ], - "sha1": "15884b8d34208b933c4319248220797995363a4c", + "sha1": "b4998a49cb6282b601fe5a1c784f1f7a01353d95", "gitDir": "test/corpus/repos/javascript", - "sha2": "a85e48b940d5259b7690df8c59df1a5bb6052d16" + "sha2": "aed8db8659025ab4f77fcadeb6fa78617942c1c1" } ,{ "testCaseDescription": "javascript-false-delete-rest-test", @@ -310,7 +310,7 @@ "filePaths": [ "false.js" ], - "sha1": "a85e48b940d5259b7690df8c59df1a5bb6052d16", + "sha1": "aed8db8659025ab4f77fcadeb6fa78617942c1c1", "gitDir": "test/corpus/repos/javascript", - "sha2": "3c4c5929ba3cb9bc23b211787745791de8774d2d" + "sha2": "83627007e919d5e812d83d6d96953a00e81369c0" }] diff --git a/test/corpus/diff-summaries/javascript/for-in-statement.json b/test/corpus/diff-summaries/javascript/for-in-statement.json index d1b9b6708..d135613ff 100644 --- a/test/corpus/diff-summaries/javascript/for-in-statement.json +++ b/test/corpus/diff-summaries/javascript/for-in-statement.json @@ -27,9 +27,9 @@ "filePaths": [ "for-in-statement.js" ], - "sha1": "215eb7570ac9ccb686598ee7a6c1ddc9c0562224", + "sha1": "67dfbd7b45236e87dcd260ea7ac3c14b307c474f", "gitDir": "test/corpus/repos/javascript", - "sha2": "a2be2a6bc55d7d2613d647e725e39fe79fd1ca21" + "sha2": "19dc2045717a1f9514c2499039d442ab79bfd4a6" } ,{ "testCaseDescription": "javascript-for-in-statement-replacement-insert-test", @@ -77,9 +77,9 @@ "filePaths": [ "for-in-statement.js" ], - "sha1": "a2be2a6bc55d7d2613d647e725e39fe79fd1ca21", + "sha1": "19dc2045717a1f9514c2499039d442ab79bfd4a6", "gitDir": "test/corpus/repos/javascript", - "sha2": "aa607b9e541223522cd47ab5d98b1289df8033db" + "sha2": "7395f4cca91248937b82d2fc067af9df623531b2" } ,{ "testCaseDescription": "javascript-for-in-statement-delete-insert-test", @@ -183,9 +183,9 @@ "filePaths": [ "for-in-statement.js" ], - "sha1": "aa607b9e541223522cd47ab5d98b1289df8033db", + "sha1": "7395f4cca91248937b82d2fc067af9df623531b2", "gitDir": "test/corpus/repos/javascript", - "sha2": "eaa14214e9d18894bf7f44347a1edc4a95966930" + "sha2": "894b6a15cc88919d0447f0fac7474905e8d3a47a" } ,{ "testCaseDescription": "javascript-for-in-statement-replacement-test", @@ -289,9 +289,9 @@ "filePaths": [ "for-in-statement.js" ], - "sha1": "eaa14214e9d18894bf7f44347a1edc4a95966930", + "sha1": "894b6a15cc88919d0447f0fac7474905e8d3a47a", "gitDir": "test/corpus/repos/javascript", - "sha2": "6007528cd72aa56e2f887a611c1b30ab2d922894" + "sha2": "441fa10580c23888485006cbf55fab3d45c7174a" } ,{ "testCaseDescription": "javascript-for-in-statement-delete-replacement-test", @@ -356,9 +356,9 @@ "filePaths": [ "for-in-statement.js" ], - "sha1": "6007528cd72aa56e2f887a611c1b30ab2d922894", + "sha1": "441fa10580c23888485006cbf55fab3d45c7174a", "gitDir": "test/corpus/repos/javascript", - "sha2": "9055c5f91ede476dde3667d3beabfc9e6ec1aa10" + "sha2": "c0fe338eebebf02a5e8565dbd13c703b61fcba53" } ,{ "testCaseDescription": "javascript-for-in-statement-delete-test", @@ -389,9 +389,9 @@ "filePaths": [ "for-in-statement.js" ], - "sha1": "9055c5f91ede476dde3667d3beabfc9e6ec1aa10", + "sha1": "c0fe338eebebf02a5e8565dbd13c703b61fcba53", "gitDir": "test/corpus/repos/javascript", - "sha2": "735ef2f75ff02bc497757685245f4fdc59422392" + "sha2": "0706b7a9ebeff341744499a50b6d8731ce528c28" } ,{ "testCaseDescription": "javascript-for-in-statement-delete-rest-test", @@ -422,7 +422,7 @@ "filePaths": [ "for-in-statement.js" ], - "sha1": "735ef2f75ff02bc497757685245f4fdc59422392", + "sha1": "0706b7a9ebeff341744499a50b6d8731ce528c28", "gitDir": "test/corpus/repos/javascript", - "sha2": "1ad3455503bfb6621a6b418f015349c2bd2a957d" + "sha2": "0ce3d1634f59a931d031cceac08ce3ea5e009bcd" }] diff --git a/test/corpus/diff-summaries/javascript/for-loop-with-in-statement.json b/test/corpus/diff-summaries/javascript/for-loop-with-in-statement.json index 6c104b60f..79bf98b52 100644 --- a/test/corpus/diff-summaries/javascript/for-loop-with-in-statement.json +++ b/test/corpus/diff-summaries/javascript/for-loop-with-in-statement.json @@ -27,9 +27,9 @@ "filePaths": [ "for-loop-with-in-statement.js" ], - "sha1": "1b5320f27fdf477cf7624573d5a594035788a73a", + "sha1": "312b5471c29b4f453f6c99ef1d2b0192b8075191", "gitDir": "test/corpus/repos/javascript", - "sha2": "55e3c4b83a742572f51eea0548a8c0e3765fab29" + "sha2": "737c5203d4608c368579f6972a34df1ae804037a" } ,{ "testCaseDescription": "javascript-for-loop-with-in-statement-replacement-insert-test", @@ -77,9 +77,9 @@ "filePaths": [ "for-loop-with-in-statement.js" ], - "sha1": "55e3c4b83a742572f51eea0548a8c0e3765fab29", + "sha1": "737c5203d4608c368579f6972a34df1ae804037a", "gitDir": "test/corpus/repos/javascript", - "sha2": "7fddb9aa46f4597ac5990bbb7ca0ef6d387030e3" + "sha2": "4c777e89f1e9772f566cd5f163e9065c67eb3e59" } ,{ "testCaseDescription": "javascript-for-loop-with-in-statement-delete-insert-test", @@ -153,9 +153,9 @@ "filePaths": [ "for-loop-with-in-statement.js" ], - "sha1": "7fddb9aa46f4597ac5990bbb7ca0ef6d387030e3", + "sha1": "4c777e89f1e9772f566cd5f163e9065c67eb3e59", "gitDir": "test/corpus/repos/javascript", - "sha2": "75afe5fde93638685d3adcc62ef9873c3d205763" + "sha2": "65a3a5c3cdd175168e8b86559dff2915718dfa82" } ,{ "testCaseDescription": "javascript-for-loop-with-in-statement-replacement-test", @@ -229,9 +229,9 @@ "filePaths": [ "for-loop-with-in-statement.js" ], - "sha1": "75afe5fde93638685d3adcc62ef9873c3d205763", + "sha1": "65a3a5c3cdd175168e8b86559dff2915718dfa82", "gitDir": "test/corpus/repos/javascript", - "sha2": "b03ca870560b98ad347ac2594813a35ef0553dce" + "sha2": "75d9025eb499683a7dabdbf36451a364d19fa48b" } ,{ "testCaseDescription": "javascript-for-loop-with-in-statement-delete-replacement-test", @@ -296,9 +296,9 @@ "filePaths": [ "for-loop-with-in-statement.js" ], - "sha1": "b03ca870560b98ad347ac2594813a35ef0553dce", + "sha1": "75d9025eb499683a7dabdbf36451a364d19fa48b", "gitDir": "test/corpus/repos/javascript", - "sha2": "6d1feba84dcea819e587e5b89f199ada2fb80c4a" + "sha2": "5041bf027b4df79e923ee65f98cf74575c5bd185" } ,{ "testCaseDescription": "javascript-for-loop-with-in-statement-delete-test", @@ -329,9 +329,9 @@ "filePaths": [ "for-loop-with-in-statement.js" ], - "sha1": "6d1feba84dcea819e587e5b89f199ada2fb80c4a", + "sha1": "5041bf027b4df79e923ee65f98cf74575c5bd185", "gitDir": "test/corpus/repos/javascript", - "sha2": "dbe96e06dcfc57ed5f62e1ea8c3f7047030cbc10" + "sha2": "8dffc803eab5d37b821f227e27ab2a628c4e79c6" } ,{ "testCaseDescription": "javascript-for-loop-with-in-statement-delete-rest-test", @@ -362,7 +362,7 @@ "filePaths": [ "for-loop-with-in-statement.js" ], - "sha1": "dbe96e06dcfc57ed5f62e1ea8c3f7047030cbc10", + "sha1": "8dffc803eab5d37b821f227e27ab2a628c4e79c6", "gitDir": "test/corpus/repos/javascript", - "sha2": "2469dee56808315df426b5a3b5c3f45a32a5dead" + "sha2": "da728273440e826c2fe2b916bce916b15b943590" }] diff --git a/test/corpus/diff-summaries/javascript/for-of-statement.json b/test/corpus/diff-summaries/javascript/for-of-statement.json index 9b9648080..31cefdf15 100644 --- a/test/corpus/diff-summaries/javascript/for-of-statement.json +++ b/test/corpus/diff-summaries/javascript/for-of-statement.json @@ -27,9 +27,9 @@ "filePaths": [ "for-of-statement.js" ], - "sha1": "2469dee56808315df426b5a3b5c3f45a32a5dead", + "sha1": "da728273440e826c2fe2b916bce916b15b943590", "gitDir": "test/corpus/repos/javascript", - "sha2": "cbe403e75ef47b35c182df6b7afe73ad796fab8a" + "sha2": "7c34377494c9c6e85107ded6606d04476c2b2268" } ,{ "testCaseDescription": "javascript-for-of-statement-replacement-insert-test", @@ -77,9 +77,9 @@ "filePaths": [ "for-of-statement.js" ], - "sha1": "cbe403e75ef47b35c182df6b7afe73ad796fab8a", + "sha1": "7c34377494c9c6e85107ded6606d04476c2b2268", "gitDir": "test/corpus/repos/javascript", - "sha2": "155a0705e326c3ff582ee652fed52550677570a6" + "sha2": "826976cafe522d197bca1e54505385f9927a93df" } ,{ "testCaseDescription": "javascript-for-of-statement-delete-insert-test", @@ -183,9 +183,9 @@ "filePaths": [ "for-of-statement.js" ], - "sha1": "155a0705e326c3ff582ee652fed52550677570a6", + "sha1": "826976cafe522d197bca1e54505385f9927a93df", "gitDir": "test/corpus/repos/javascript", - "sha2": "ef8d8643334cebf32c2c4be0f8efab6bc8efbc2b" + "sha2": "f62dd3dacb19116d9b248549e23eff65b07a94a7" } ,{ "testCaseDescription": "javascript-for-of-statement-replacement-test", @@ -289,9 +289,9 @@ "filePaths": [ "for-of-statement.js" ], - "sha1": "ef8d8643334cebf32c2c4be0f8efab6bc8efbc2b", + "sha1": "f62dd3dacb19116d9b248549e23eff65b07a94a7", "gitDir": "test/corpus/repos/javascript", - "sha2": "fca6551e597967f1b7970eba8647ea449d642c0d" + "sha2": "65962e4817eecea21c95026afd9cb40387aaa657" } ,{ "testCaseDescription": "javascript-for-of-statement-delete-replacement-test", @@ -356,9 +356,9 @@ "filePaths": [ "for-of-statement.js" ], - "sha1": "fca6551e597967f1b7970eba8647ea449d642c0d", + "sha1": "65962e4817eecea21c95026afd9cb40387aaa657", "gitDir": "test/corpus/repos/javascript", - "sha2": "951e6473bd1c1c48a8ccf17b85edf71c30f68003" + "sha2": "44a40ac1376d641124b097e8a6e1e2d9b12c991c" } ,{ "testCaseDescription": "javascript-for-of-statement-delete-test", @@ -389,9 +389,9 @@ "filePaths": [ "for-of-statement.js" ], - "sha1": "951e6473bd1c1c48a8ccf17b85edf71c30f68003", + "sha1": "44a40ac1376d641124b097e8a6e1e2d9b12c991c", "gitDir": "test/corpus/repos/javascript", - "sha2": "eb9af080f71a3ebd4faf827ba73ca5506a0078bb" + "sha2": "c7c2ac9ea4db0fb48c75d5fbf756f4474054d0fe" } ,{ "testCaseDescription": "javascript-for-of-statement-delete-rest-test", @@ -422,7 +422,7 @@ "filePaths": [ "for-of-statement.js" ], - "sha1": "eb9af080f71a3ebd4faf827ba73ca5506a0078bb", + "sha1": "c7c2ac9ea4db0fb48c75d5fbf756f4474054d0fe", "gitDir": "test/corpus/repos/javascript", - "sha2": "4baec39517b6fe2e913b63502b66c0f5bb4ad2cc" + "sha2": "7f97f2e3a13baab2548b10a72e291b71ca0b9fa4" }] diff --git a/test/corpus/diff-summaries/javascript/for-statement.json b/test/corpus/diff-summaries/javascript/for-statement.json index e407c3150..41443f789 100644 --- a/test/corpus/diff-summaries/javascript/for-statement.json +++ b/test/corpus/diff-summaries/javascript/for-statement.json @@ -27,9 +27,9 @@ "filePaths": [ "for-statement.js" ], - "sha1": "8c6579c037e31738b4decb4405d7a17824524ca3", + "sha1": "b7399e257e9ce0b28ce3080ac7e8edb2778614a3", "gitDir": "test/corpus/repos/javascript", - "sha2": "8acb9b3de3ca8787d948acb4a99f00d03cee5b3e" + "sha2": "d476b0d1ac0e6db2068623c1f59607edebcaca08" } ,{ "testCaseDescription": "javascript-for-statement-replacement-insert-test", @@ -77,9 +77,9 @@ "filePaths": [ "for-statement.js" ], - "sha1": "8acb9b3de3ca8787d948acb4a99f00d03cee5b3e", + "sha1": "d476b0d1ac0e6db2068623c1f59607edebcaca08", "gitDir": "test/corpus/repos/javascript", - "sha2": "8e51e424b4a6aca62377fa98a82aeaa8e9ddce55" + "sha2": "ca52f8da99ea8e209eb129dd6d8433b56a6eee30" } ,{ "testCaseDescription": "javascript-for-statement-delete-insert-test", @@ -123,9 +123,9 @@ "filePaths": [ "for-statement.js" ], - "sha1": "8e51e424b4a6aca62377fa98a82aeaa8e9ddce55", + "sha1": "ca52f8da99ea8e209eb129dd6d8433b56a6eee30", "gitDir": "test/corpus/repos/javascript", - "sha2": "c0acf9cf01a97524f0c44297d9f448881a381f67" + "sha2": "f76f9890979255661b54a280596c95f979dbeab0" } ,{ "testCaseDescription": "javascript-for-statement-replacement-test", @@ -169,9 +169,9 @@ "filePaths": [ "for-statement.js" ], - "sha1": "c0acf9cf01a97524f0c44297d9f448881a381f67", + "sha1": "f76f9890979255661b54a280596c95f979dbeab0", "gitDir": "test/corpus/repos/javascript", - "sha2": "5253024f0a55122448f8b16a6869686fcb3b9fa1" + "sha2": "91a63fdc213376bcf0dfb8a6d8c0ce895acdcd91" } ,{ "testCaseDescription": "javascript-for-statement-delete-replacement-test", @@ -236,9 +236,9 @@ "filePaths": [ "for-statement.js" ], - "sha1": "5253024f0a55122448f8b16a6869686fcb3b9fa1", + "sha1": "91a63fdc213376bcf0dfb8a6d8c0ce895acdcd91", "gitDir": "test/corpus/repos/javascript", - "sha2": "3a720565a0493ccf4374590f8b8314b29d642fa0" + "sha2": "b8a203be1d315305a0d3e8e92700adf18f64cfb8" } ,{ "testCaseDescription": "javascript-for-statement-delete-test", @@ -269,9 +269,9 @@ "filePaths": [ "for-statement.js" ], - "sha1": "3a720565a0493ccf4374590f8b8314b29d642fa0", + "sha1": "b8a203be1d315305a0d3e8e92700adf18f64cfb8", "gitDir": "test/corpus/repos/javascript", - "sha2": "2fbfe01a9a42d1f7bc719d35bc67e51164dfac6c" + "sha2": "18cdc03ac4c49a1dafaa9f510dfb157efa7967ce" } ,{ "testCaseDescription": "javascript-for-statement-delete-rest-test", @@ -302,7 +302,7 @@ "filePaths": [ "for-statement.js" ], - "sha1": "2fbfe01a9a42d1f7bc719d35bc67e51164dfac6c", + "sha1": "18cdc03ac4c49a1dafaa9f510dfb157efa7967ce", "gitDir": "test/corpus/repos/javascript", - "sha2": "1689419def381340a06222171173117f80ab169e" + "sha2": "031c53cff6b8f106847a7cd1da37a95d714890e3" }] diff --git a/test/corpus/diff-summaries/javascript/function-call-args.json b/test/corpus/diff-summaries/javascript/function-call-args.json index 8dd954247..0cb749ed6 100644 --- a/test/corpus/diff-summaries/javascript/function-call-args.json +++ b/test/corpus/diff-summaries/javascript/function-call-args.json @@ -27,9 +27,9 @@ "filePaths": [ "function-call-args.js" ], - "sha1": "7a9cdc6c356ec1e7fe6e47c923898d3e2e6a32cc", + "sha1": "d40eaae205d67245d41875f45a6cd12cc1c6beee", "gitDir": "test/corpus/repos/javascript", - "sha2": "183f0fed6e757160eafedb9d7740cdfdb28bec21" + "sha2": "dbcc4e50275e5bd1f0511f2059f6018b692c1a9d" } ,{ "testCaseDescription": "javascript-function-call-args-replacement-insert-test", @@ -77,9 +77,9 @@ "filePaths": [ "function-call-args.js" ], - "sha1": "183f0fed6e757160eafedb9d7740cdfdb28bec21", + "sha1": "dbcc4e50275e5bd1f0511f2059f6018b692c1a9d", "gitDir": "test/corpus/repos/javascript", - "sha2": "b30012eb0ae7cdbcb6a55ce2ada5ead28b4d09d5" + "sha2": "9a93f870384dadd725f96f57760349595f4e127a" } ,{ "testCaseDescription": "javascript-function-call-args-delete-insert-test", @@ -273,9 +273,9 @@ "filePaths": [ "function-call-args.js" ], - "sha1": "b30012eb0ae7cdbcb6a55ce2ada5ead28b4d09d5", + "sha1": "9a93f870384dadd725f96f57760349595f4e127a", "gitDir": "test/corpus/repos/javascript", - "sha2": "1f00971ae667503452bec939433970cf2f5a1ef9" + "sha2": "069e5afce34c258c628d975edbfecd34ed9d954e" } ,{ "testCaseDescription": "javascript-function-call-args-replacement-test", @@ -469,9 +469,9 @@ "filePaths": [ "function-call-args.js" ], - "sha1": "1f00971ae667503452bec939433970cf2f5a1ef9", + "sha1": "069e5afce34c258c628d975edbfecd34ed9d954e", "gitDir": "test/corpus/repos/javascript", - "sha2": "7f80f26bf5f8baacf47c9d7ad830572b46738b56" + "sha2": "139330bfd11d844cfabefefecc39fa56286b0e23" } ,{ "testCaseDescription": "javascript-function-call-args-delete-replacement-test", @@ -536,9 +536,9 @@ "filePaths": [ "function-call-args.js" ], - "sha1": "7f80f26bf5f8baacf47c9d7ad830572b46738b56", + "sha1": "139330bfd11d844cfabefefecc39fa56286b0e23", "gitDir": "test/corpus/repos/javascript", - "sha2": "3e16e4bb994195b7c5a841f3e585c332c7aaf578" + "sha2": "75bba8bbefbc3c66e14874571923e76553675938" } ,{ "testCaseDescription": "javascript-function-call-args-delete-test", @@ -569,9 +569,9 @@ "filePaths": [ "function-call-args.js" ], - "sha1": "3e16e4bb994195b7c5a841f3e585c332c7aaf578", + "sha1": "75bba8bbefbc3c66e14874571923e76553675938", "gitDir": "test/corpus/repos/javascript", - "sha2": "091f7c6596e348e44e3679375e57eddc657a73a3" + "sha2": "8a50fbb89f4afe308701d23df566f1342ef25ca2" } ,{ "testCaseDescription": "javascript-function-call-args-delete-rest-test", @@ -602,7 +602,7 @@ "filePaths": [ "function-call-args.js" ], - "sha1": "091f7c6596e348e44e3679375e57eddc657a73a3", + "sha1": "8a50fbb89f4afe308701d23df566f1342ef25ca2", "gitDir": "test/corpus/repos/javascript", - "sha2": "e67227e82c01378ae1102d7579e52a47e06ef16a" + "sha2": "143f944ead8b453c8d4f2a24f35b6e64406217ff" }] diff --git a/test/corpus/diff-summaries/javascript/function-call.json b/test/corpus/diff-summaries/javascript/function-call.json index a4341f8be..54ce23f3a 100644 --- a/test/corpus/diff-summaries/javascript/function-call.json +++ b/test/corpus/diff-summaries/javascript/function-call.json @@ -27,9 +27,9 @@ "filePaths": [ "function-call.js" ], - "sha1": "66f76d6c6d3a517f3f4c016d8e03d3497cf724c6", + "sha1": "adef6baf8b5eef8703844039dc7001ac32c9ce46", "gitDir": "test/corpus/repos/javascript", - "sha2": "04ae6b563749c2b0fcca12174eb5398356c67a8e" + "sha2": "e4c539759e2c91c5b34dcba8f3406fd8aa0cc054" } ,{ "testCaseDescription": "javascript-function-call-replacement-insert-test", @@ -77,9 +77,9 @@ "filePaths": [ "function-call.js" ], - "sha1": "04ae6b563749c2b0fcca12174eb5398356c67a8e", + "sha1": "e4c539759e2c91c5b34dcba8f3406fd8aa0cc054", "gitDir": "test/corpus/repos/javascript", - "sha2": "f6af23e39ba5fd5b1d1733db2141a70d65534f41" + "sha2": "d6eb3328bdac66cf529be27130320aeaf98970dd" } ,{ "testCaseDescription": "javascript-function-call-delete-insert-test", @@ -123,9 +123,9 @@ "filePaths": [ "function-call.js" ], - "sha1": "f6af23e39ba5fd5b1d1733db2141a70d65534f41", + "sha1": "d6eb3328bdac66cf529be27130320aeaf98970dd", "gitDir": "test/corpus/repos/javascript", - "sha2": "f6c31c3c422ab05b2d0bba725022eeabcaa3739f" + "sha2": "7bfcd385b7161aa142a8e3fd1a2e1448d68ff613" } ,{ "testCaseDescription": "javascript-function-call-replacement-test", @@ -169,9 +169,9 @@ "filePaths": [ "function-call.js" ], - "sha1": "f6c31c3c422ab05b2d0bba725022eeabcaa3739f", + "sha1": "7bfcd385b7161aa142a8e3fd1a2e1448d68ff613", "gitDir": "test/corpus/repos/javascript", - "sha2": "14e9613f11bf3b30e519ca68df0c2f4a9f153c40" + "sha2": "47b274338bb9a56dd07d19a8bdc0183ce6ee12f3" } ,{ "testCaseDescription": "javascript-function-call-delete-replacement-test", @@ -236,9 +236,9 @@ "filePaths": [ "function-call.js" ], - "sha1": "14e9613f11bf3b30e519ca68df0c2f4a9f153c40", + "sha1": "47b274338bb9a56dd07d19a8bdc0183ce6ee12f3", "gitDir": "test/corpus/repos/javascript", - "sha2": "b8c0d83eeb28bd56aacfca81580c8e3217da7345" + "sha2": "8b098f878ef245b8ddba276e26cf8604ce2bd54d" } ,{ "testCaseDescription": "javascript-function-call-delete-test", @@ -269,9 +269,9 @@ "filePaths": [ "function-call.js" ], - "sha1": "b8c0d83eeb28bd56aacfca81580c8e3217da7345", + "sha1": "8b098f878ef245b8ddba276e26cf8604ce2bd54d", "gitDir": "test/corpus/repos/javascript", - "sha2": "27dba7ea895c481db1cd34b80cf0ef484c718882" + "sha2": "97d178bec7c2a1cff159923c7e4e9626512b5f45" } ,{ "testCaseDescription": "javascript-function-call-delete-rest-test", @@ -302,7 +302,7 @@ "filePaths": [ "function-call.js" ], - "sha1": "27dba7ea895c481db1cd34b80cf0ef484c718882", + "sha1": "97d178bec7c2a1cff159923c7e4e9626512b5f45", "gitDir": "test/corpus/repos/javascript", - "sha2": "bde44008cfb326f395ddb1071a073fc1113ffb3d" + "sha2": "ec567b366ed73c0a2d60e9e3a7736db883537a4c" }] diff --git a/test/corpus/diff-summaries/javascript/function.json b/test/corpus/diff-summaries/javascript/function.json index cd35b2444..f5b66722a 100644 --- a/test/corpus/diff-summaries/javascript/function.json +++ b/test/corpus/diff-summaries/javascript/function.json @@ -27,9 +27,9 @@ "filePaths": [ "function.js" ], - "sha1": "7421caaeb3a46acf3fd36871e3fd56e4409df4c1", + "sha1": "0ee9c8e6c87189715a67160428ce11ee61012b05", "gitDir": "test/corpus/repos/javascript", - "sha2": "9eb28dc8e67375a2846a0a2baa6f91de7a54e3fc" + "sha2": "3d7a4969e8fb9d9ece8949c38a69623bfa9892e2" } ,{ "testCaseDescription": "javascript-function-replacement-insert-test", @@ -77,9 +77,9 @@ "filePaths": [ "function.js" ], - "sha1": "9eb28dc8e67375a2846a0a2baa6f91de7a54e3fc", + "sha1": "3d7a4969e8fb9d9ece8949c38a69623bfa9892e2", "gitDir": "test/corpus/repos/javascript", - "sha2": "f80644c146243f36bc8d53bd88b463f88fb56148" + "sha2": "61be4363b488b3f1270c51d76a861b0520d11a43" } ,{ "testCaseDescription": "javascript-function-delete-insert-test", @@ -123,9 +123,9 @@ "filePaths": [ "function.js" ], - "sha1": "f80644c146243f36bc8d53bd88b463f88fb56148", + "sha1": "61be4363b488b3f1270c51d76a861b0520d11a43", "gitDir": "test/corpus/repos/javascript", - "sha2": "16e3dd70bc83125385a9b3f952e77b24b15558cd" + "sha2": "5e3d0e9170ce7aa9d264d024ac81625983a7061c" } ,{ "testCaseDescription": "javascript-function-replacement-test", @@ -169,9 +169,9 @@ "filePaths": [ "function.js" ], - "sha1": "16e3dd70bc83125385a9b3f952e77b24b15558cd", + "sha1": "5e3d0e9170ce7aa9d264d024ac81625983a7061c", "gitDir": "test/corpus/repos/javascript", - "sha2": "610b235fd79ed384ca2ed512957629b75fdaec56" + "sha2": "5bd30701955a385c366e9a64f7403ed0330f688f" } ,{ "testCaseDescription": "javascript-function-delete-replacement-test", @@ -236,9 +236,9 @@ "filePaths": [ "function.js" ], - "sha1": "610b235fd79ed384ca2ed512957629b75fdaec56", + "sha1": "5bd30701955a385c366e9a64f7403ed0330f688f", "gitDir": "test/corpus/repos/javascript", - "sha2": "c11cac612eb21c4dd32f29b5fdcbb77431bc1478" + "sha2": "78bd9a251692c8c72fea22b7a64540cbce201c52" } ,{ "testCaseDescription": "javascript-function-delete-test", @@ -269,9 +269,9 @@ "filePaths": [ "function.js" ], - "sha1": "c11cac612eb21c4dd32f29b5fdcbb77431bc1478", + "sha1": "78bd9a251692c8c72fea22b7a64540cbce201c52", "gitDir": "test/corpus/repos/javascript", - "sha2": "dfa9a3bf7f53d0621d490ae446682bcf37e6c2b9" + "sha2": "a7ed42c65188f70e530b0c2c16307a78612a925c" } ,{ "testCaseDescription": "javascript-function-delete-rest-test", @@ -302,7 +302,7 @@ "filePaths": [ "function.js" ], - "sha1": "dfa9a3bf7f53d0621d490ae446682bcf37e6c2b9", + "sha1": "a7ed42c65188f70e530b0c2c16307a78612a925c", "gitDir": "test/corpus/repos/javascript", - "sha2": "1331d4ffb544aebfa16c17c9c2ebbab19e6f422a" + "sha2": "292d11c2e4263aedc5c5b54a527d686428f8ddd1" }] diff --git a/test/corpus/diff-summaries/javascript/generator-function.json b/test/corpus/diff-summaries/javascript/generator-function.json index 89d303361..da5471d31 100644 --- a/test/corpus/diff-summaries/javascript/generator-function.json +++ b/test/corpus/diff-summaries/javascript/generator-function.json @@ -27,9 +27,9 @@ "filePaths": [ "generator-function.js" ], - "sha1": "4d63196a05b9443aebe166c10eaf31d60a162f7e", + "sha1": "ea881b604fbd6a7bff63837b413fbb2878da9525", "gitDir": "test/corpus/repos/javascript", - "sha2": "36b15111da4c3d7db3722d53889c04ec06472bf7" + "sha2": "7c4756fa11806d6f8885f4de45d34547c379a06d" } ,{ "testCaseDescription": "javascript-generator-function-replacement-insert-test", @@ -77,9 +77,9 @@ "filePaths": [ "generator-function.js" ], - "sha1": "36b15111da4c3d7db3722d53889c04ec06472bf7", + "sha1": "7c4756fa11806d6f8885f4de45d34547c379a06d", "gitDir": "test/corpus/repos/javascript", - "sha2": "4c88f30a1529bc19cf1c5f0e96db7046c3020301" + "sha2": "60487f9057321582a5566de225346fd4bc7712c5" } ,{ "testCaseDescription": "javascript-generator-function-delete-insert-test", @@ -123,9 +123,9 @@ "filePaths": [ "generator-function.js" ], - "sha1": "4c88f30a1529bc19cf1c5f0e96db7046c3020301", + "sha1": "60487f9057321582a5566de225346fd4bc7712c5", "gitDir": "test/corpus/repos/javascript", - "sha2": "a688e4e430dca4e71ee900724635db302ea27a0a" + "sha2": "837d5d77bc3bc5f98fd4aa68fed39b57ca5fb726" } ,{ "testCaseDescription": "javascript-generator-function-replacement-test", @@ -169,9 +169,9 @@ "filePaths": [ "generator-function.js" ], - "sha1": "a688e4e430dca4e71ee900724635db302ea27a0a", + "sha1": "837d5d77bc3bc5f98fd4aa68fed39b57ca5fb726", "gitDir": "test/corpus/repos/javascript", - "sha2": "39e1e3960d0368f451e694779a82ef34e1a9270b" + "sha2": "535bcb4bd86100564b864040688a0812943335ec" } ,{ "testCaseDescription": "javascript-generator-function-delete-replacement-test", @@ -236,9 +236,9 @@ "filePaths": [ "generator-function.js" ], - "sha1": "39e1e3960d0368f451e694779a82ef34e1a9270b", + "sha1": "535bcb4bd86100564b864040688a0812943335ec", "gitDir": "test/corpus/repos/javascript", - "sha2": "782a8e72f3f39f9557c1b5653ddec71dcdd5fb56" + "sha2": "3c2b85be7773dc10e47c51a89c9c63f9248f9b4d" } ,{ "testCaseDescription": "javascript-generator-function-delete-test", @@ -269,9 +269,9 @@ "filePaths": [ "generator-function.js" ], - "sha1": "782a8e72f3f39f9557c1b5653ddec71dcdd5fb56", + "sha1": "3c2b85be7773dc10e47c51a89c9c63f9248f9b4d", "gitDir": "test/corpus/repos/javascript", - "sha2": "f88a7087ddff6c06546b3e0124f7ca8d94d409f8" + "sha2": "6527df68974335620c22e86b950f2af102a9cf32" } ,{ "testCaseDescription": "javascript-generator-function-delete-rest-test", @@ -302,7 +302,7 @@ "filePaths": [ "generator-function.js" ], - "sha1": "f88a7087ddff6c06546b3e0124f7ca8d94d409f8", + "sha1": "6527df68974335620c22e86b950f2af102a9cf32", "gitDir": "test/corpus/repos/javascript", - "sha2": "5fe4477fe4c9d164946d8aaf8fe66f107b0901b4" + "sha2": "5921bfd9de54f2a9868741666cba1c6fb5c4487a" }] diff --git a/test/corpus/diff-summaries/javascript/identifier.json b/test/corpus/diff-summaries/javascript/identifier.json index 0cc55db05..2b3251eb9 100644 --- a/test/corpus/diff-summaries/javascript/identifier.json +++ b/test/corpus/diff-summaries/javascript/identifier.json @@ -27,9 +27,9 @@ "filePaths": [ "identifier.js" ], - "sha1": "8bed39ae9a7d7acce7400df7173470825fa46cb0", + "sha1": "1917c441d2b5dc77f63539a5df1e3cd7f0df97f3", "gitDir": "test/corpus/repos/javascript", - "sha2": "adad30bc5133d1c447dc340517b42feaf646ba53" + "sha2": "dabf0b766bc1e9078802788c75696638b135bba4" } ,{ "testCaseDescription": "javascript-identifier-replacement-insert-test", @@ -77,9 +77,9 @@ "filePaths": [ "identifier.js" ], - "sha1": "adad30bc5133d1c447dc340517b42feaf646ba53", + "sha1": "dabf0b766bc1e9078802788c75696638b135bba4", "gitDir": "test/corpus/repos/javascript", - "sha2": "0c71a54b8d1ef900aed495431e66ca7e1aabda5c" + "sha2": "9a6ae9eaf5793972dbd956934afece901c3585de" } ,{ "testCaseDescription": "javascript-identifier-delete-insert-test", @@ -123,9 +123,9 @@ "filePaths": [ "identifier.js" ], - "sha1": "0c71a54b8d1ef900aed495431e66ca7e1aabda5c", + "sha1": "9a6ae9eaf5793972dbd956934afece901c3585de", "gitDir": "test/corpus/repos/javascript", - "sha2": "f5b7d7c4e2697f8512daa4cbc1b98b1a08cf12ec" + "sha2": "d47d4ca7f6adc50a478c132c0322581c6a97d9ba" } ,{ "testCaseDescription": "javascript-identifier-replacement-test", @@ -169,9 +169,9 @@ "filePaths": [ "identifier.js" ], - "sha1": "f5b7d7c4e2697f8512daa4cbc1b98b1a08cf12ec", + "sha1": "d47d4ca7f6adc50a478c132c0322581c6a97d9ba", "gitDir": "test/corpus/repos/javascript", - "sha2": "316ee9b49a7790b81670a4d92a78ab982df69c03" + "sha2": "cd4983604bbfbb1d68b3c3aa269b44bb18e7ec19" } ,{ "testCaseDescription": "javascript-identifier-delete-replacement-test", @@ -236,9 +236,9 @@ "filePaths": [ "identifier.js" ], - "sha1": "316ee9b49a7790b81670a4d92a78ab982df69c03", + "sha1": "cd4983604bbfbb1d68b3c3aa269b44bb18e7ec19", "gitDir": "test/corpus/repos/javascript", - "sha2": "78d921b09f5d8adc2a6fa113a032252aca288d47" + "sha2": "f485b85280aefcea21b662c09b093cbe8bd7235b" } ,{ "testCaseDescription": "javascript-identifier-delete-test", @@ -269,9 +269,9 @@ "filePaths": [ "identifier.js" ], - "sha1": "78d921b09f5d8adc2a6fa113a032252aca288d47", + "sha1": "f485b85280aefcea21b662c09b093cbe8bd7235b", "gitDir": "test/corpus/repos/javascript", - "sha2": "beb075d5569a09221ee45c35159e37ac9d9cec4c" + "sha2": "e88e8ecf1d1356117505cd93c05985d9d9f7309a" } ,{ "testCaseDescription": "javascript-identifier-delete-rest-test", @@ -302,7 +302,7 @@ "filePaths": [ "identifier.js" ], - "sha1": "beb075d5569a09221ee45c35159e37ac9d9cec4c", + "sha1": "e88e8ecf1d1356117505cd93c05985d9d9f7309a", "gitDir": "test/corpus/repos/javascript", - "sha2": "7a8a0da7d72fa0fc4f17e0877fbf7991771801e4" + "sha2": "324ef3f6d6409ee7a42609453d3259490538a470" }] diff --git a/test/corpus/diff-summaries/javascript/if-else.json b/test/corpus/diff-summaries/javascript/if-else.json index 2a4a66e17..9239cdd3d 100644 --- a/test/corpus/diff-summaries/javascript/if-else.json +++ b/test/corpus/diff-summaries/javascript/if-else.json @@ -27,9 +27,9 @@ "filePaths": [ "if-else.js" ], - "sha1": "a6070e9c94930a94f1913e69bef6da80923cbfde", + "sha1": "3e202ca64adc48c6445568834fbe8f9105a129f0", "gitDir": "test/corpus/repos/javascript", - "sha2": "e6b1c046a9f61b81b0646a0d24ce02db7f461209" + "sha2": "b4bb0651e765474189de720cc0d931b95cd0e240" } ,{ "testCaseDescription": "javascript-if-else-replacement-insert-test", @@ -77,9 +77,9 @@ "filePaths": [ "if-else.js" ], - "sha1": "e6b1c046a9f61b81b0646a0d24ce02db7f461209", + "sha1": "b4bb0651e765474189de720cc0d931b95cd0e240", "gitDir": "test/corpus/repos/javascript", - "sha2": "8c1d085746a786b9f1f97a1df047a777ba9958f6" + "sha2": "91b41d08762cdeea84327cb0239acf3d9ac40e55" } ,{ "testCaseDescription": "javascript-if-else-delete-insert-test", @@ -123,9 +123,9 @@ "filePaths": [ "if-else.js" ], - "sha1": "8c1d085746a786b9f1f97a1df047a777ba9958f6", + "sha1": "91b41d08762cdeea84327cb0239acf3d9ac40e55", "gitDir": "test/corpus/repos/javascript", - "sha2": "a4a9d189ba9f43fb4e56f0c5c7d26b8f24bd8fb9" + "sha2": "f067f9cc9444e7b808e9a2ad1c95f6a606410976" } ,{ "testCaseDescription": "javascript-if-else-replacement-test", @@ -169,9 +169,9 @@ "filePaths": [ "if-else.js" ], - "sha1": "a4a9d189ba9f43fb4e56f0c5c7d26b8f24bd8fb9", + "sha1": "f067f9cc9444e7b808e9a2ad1c95f6a606410976", "gitDir": "test/corpus/repos/javascript", - "sha2": "b279cca2a52da34fc8487e65af5f74d2e3d156ee" + "sha2": "7cdbeb6a95fe9419f442056395d4d15953e92af5" } ,{ "testCaseDescription": "javascript-if-else-delete-replacement-test", @@ -236,9 +236,9 @@ "filePaths": [ "if-else.js" ], - "sha1": "b279cca2a52da34fc8487e65af5f74d2e3d156ee", + "sha1": "7cdbeb6a95fe9419f442056395d4d15953e92af5", "gitDir": "test/corpus/repos/javascript", - "sha2": "13a7419cb57d66ff977bcee43d8a447cb77977ed" + "sha2": "5347af1d2f6459c4cb958ee5bf953a89bd53acc2" } ,{ "testCaseDescription": "javascript-if-else-delete-test", @@ -269,9 +269,9 @@ "filePaths": [ "if-else.js" ], - "sha1": "13a7419cb57d66ff977bcee43d8a447cb77977ed", + "sha1": "5347af1d2f6459c4cb958ee5bf953a89bd53acc2", "gitDir": "test/corpus/repos/javascript", - "sha2": "38ed00f0237ad854471e13f9a859abf746712590" + "sha2": "e02ca1db8da2f5ec33cc3e219861b5901bf8835f" } ,{ "testCaseDescription": "javascript-if-else-delete-rest-test", @@ -302,7 +302,7 @@ "filePaths": [ "if-else.js" ], - "sha1": "38ed00f0237ad854471e13f9a859abf746712590", + "sha1": "e02ca1db8da2f5ec33cc3e219861b5901bf8835f", "gitDir": "test/corpus/repos/javascript", - "sha2": "8626ab02829f07b2f15f25da58eb41b69afd53e3" + "sha2": "d3aee735401b2b9c803e3d684ab3c6b96a16898f" }] diff --git a/test/corpus/diff-summaries/javascript/if.json b/test/corpus/diff-summaries/javascript/if.json index 1568c2e60..6c13cf220 100644 --- a/test/corpus/diff-summaries/javascript/if.json +++ b/test/corpus/diff-summaries/javascript/if.json @@ -27,9 +27,9 @@ "filePaths": [ "if.js" ], - "sha1": "1fbd44cbdd925bb727f5b07af974a37db31b3ea0", + "sha1": "f4a276fc53b44233f1996fab1c4310602ddc195f", "gitDir": "test/corpus/repos/javascript", - "sha2": "d2f31345bd3ceb057e9864e3065517bd59d81e84" + "sha2": "369c257c6424bc2c1e64361d21e746e955512d30" } ,{ "testCaseDescription": "javascript-if-replacement-insert-test", @@ -77,9 +77,9 @@ "filePaths": [ "if.js" ], - "sha1": "d2f31345bd3ceb057e9864e3065517bd59d81e84", + "sha1": "369c257c6424bc2c1e64361d21e746e955512d30", "gitDir": "test/corpus/repos/javascript", - "sha2": "672d891ad62294fecaa1cb0fa0b001748053a2a7" + "sha2": "c3188f36fffcd998dd94f68b15299e784dacb393" } ,{ "testCaseDescription": "javascript-if-delete-insert-test", @@ -123,9 +123,9 @@ "filePaths": [ "if.js" ], - "sha1": "672d891ad62294fecaa1cb0fa0b001748053a2a7", + "sha1": "c3188f36fffcd998dd94f68b15299e784dacb393", "gitDir": "test/corpus/repos/javascript", - "sha2": "9a4763d83b29a8834a92126f6c9488397a34ca60" + "sha2": "5ca78ae7e4e1af2f0e530be56692a1845af1a8ac" } ,{ "testCaseDescription": "javascript-if-replacement-test", @@ -169,9 +169,9 @@ "filePaths": [ "if.js" ], - "sha1": "9a4763d83b29a8834a92126f6c9488397a34ca60", + "sha1": "5ca78ae7e4e1af2f0e530be56692a1845af1a8ac", "gitDir": "test/corpus/repos/javascript", - "sha2": "6fd20d99b1748aff8d5e068f799e9e8c4b174986" + "sha2": "0e85ea58c2ecf3ea3acdddedc1c197cac602e4fb" } ,{ "testCaseDescription": "javascript-if-delete-replacement-test", @@ -236,9 +236,9 @@ "filePaths": [ "if.js" ], - "sha1": "6fd20d99b1748aff8d5e068f799e9e8c4b174986", + "sha1": "0e85ea58c2ecf3ea3acdddedc1c197cac602e4fb", "gitDir": "test/corpus/repos/javascript", - "sha2": "39e72b13348c108e810fea6c43852c082feb83e6" + "sha2": "568c6d8ef9e1a62c53a0bd6bebdef66dab44497a" } ,{ "testCaseDescription": "javascript-if-delete-test", @@ -269,9 +269,9 @@ "filePaths": [ "if.js" ], - "sha1": "39e72b13348c108e810fea6c43852c082feb83e6", + "sha1": "568c6d8ef9e1a62c53a0bd6bebdef66dab44497a", "gitDir": "test/corpus/repos/javascript", - "sha2": "6bd2aa7a9a559c032a228e8efe94ba3088432ad5" + "sha2": "7c8a4d7ea730fffa4e149ae4b078c77283dc6f77" } ,{ "testCaseDescription": "javascript-if-delete-rest-test", @@ -302,7 +302,7 @@ "filePaths": [ "if.js" ], - "sha1": "6bd2aa7a9a559c032a228e8efe94ba3088432ad5", + "sha1": "7c8a4d7ea730fffa4e149ae4b078c77283dc6f77", "gitDir": "test/corpus/repos/javascript", - "sha2": "a6070e9c94930a94f1913e69bef6da80923cbfde" + "sha2": "3e202ca64adc48c6445568834fbe8f9105a129f0" }] diff --git a/test/corpus/diff-summaries/javascript/math-assignment-operator.json b/test/corpus/diff-summaries/javascript/math-assignment-operator.json index d0691c8a7..ea426a009 100644 --- a/test/corpus/diff-summaries/javascript/math-assignment-operator.json +++ b/test/corpus/diff-summaries/javascript/math-assignment-operator.json @@ -27,9 +27,9 @@ "filePaths": [ "math-assignment-operator.js" ], - "sha1": "de1bc70d66645688aab217b87e9d472a34e42bd1", + "sha1": "d1711a33e14ac0a6c516afdd4885511a60f6a194", "gitDir": "test/corpus/repos/javascript", - "sha2": "304dfd62cf86a774d5233356d3fbf6b8ae6a653f" + "sha2": "e6ca7254618b96bd13d5bf59abe523b6b7be0696" } ,{ "testCaseDescription": "javascript-math-assignment-operator-replacement-insert-test", @@ -77,9 +77,9 @@ "filePaths": [ "math-assignment-operator.js" ], - "sha1": "304dfd62cf86a774d5233356d3fbf6b8ae6a653f", + "sha1": "e6ca7254618b96bd13d5bf59abe523b6b7be0696", "gitDir": "test/corpus/repos/javascript", - "sha2": "6f518ab031fdda3308872804c6fe6e05a6a188b1" + "sha2": "624e4b3fcc902aad7ef2a8dd187c3504b004e01d" } ,{ "testCaseDescription": "javascript-math-assignment-operator-delete-insert-test", @@ -123,9 +123,9 @@ "filePaths": [ "math-assignment-operator.js" ], - "sha1": "6f518ab031fdda3308872804c6fe6e05a6a188b1", + "sha1": "624e4b3fcc902aad7ef2a8dd187c3504b004e01d", "gitDir": "test/corpus/repos/javascript", - "sha2": "424e6c93d8ff04eed06cec05810e174a8ef07fae" + "sha2": "21d4e2aa872d6526c9ec132d7aa405034c1d5b4e" } ,{ "testCaseDescription": "javascript-math-assignment-operator-replacement-test", @@ -169,9 +169,9 @@ "filePaths": [ "math-assignment-operator.js" ], - "sha1": "424e6c93d8ff04eed06cec05810e174a8ef07fae", + "sha1": "21d4e2aa872d6526c9ec132d7aa405034c1d5b4e", "gitDir": "test/corpus/repos/javascript", - "sha2": "4ea476b11bab26e33537bcd43da82be1b1329260" + "sha2": "849e0b35b93b33918caade8c41161658008ce343" } ,{ "testCaseDescription": "javascript-math-assignment-operator-delete-replacement-test", @@ -236,9 +236,9 @@ "filePaths": [ "math-assignment-operator.js" ], - "sha1": "4ea476b11bab26e33537bcd43da82be1b1329260", + "sha1": "849e0b35b93b33918caade8c41161658008ce343", "gitDir": "test/corpus/repos/javascript", - "sha2": "de5800f3db0450576b6b04eda1bbc145c460e524" + "sha2": "381a333198f364cf59bad22b46744c406fe5b1db" } ,{ "testCaseDescription": "javascript-math-assignment-operator-delete-test", @@ -269,9 +269,9 @@ "filePaths": [ "math-assignment-operator.js" ], - "sha1": "de5800f3db0450576b6b04eda1bbc145c460e524", + "sha1": "381a333198f364cf59bad22b46744c406fe5b1db", "gitDir": "test/corpus/repos/javascript", - "sha2": "02b55a24fd347df4ba80d54a05681ad92de48eae" + "sha2": "a8136c633b138aba118c5ca17cefb2ed101687cf" } ,{ "testCaseDescription": "javascript-math-assignment-operator-delete-rest-test", @@ -302,7 +302,7 @@ "filePaths": [ "math-assignment-operator.js" ], - "sha1": "02b55a24fd347df4ba80d54a05681ad92de48eae", + "sha1": "a8136c633b138aba118c5ca17cefb2ed101687cf", "gitDir": "test/corpus/repos/javascript", - "sha2": "1b5320f27fdf477cf7624573d5a594035788a73a" + "sha2": "312b5471c29b4f453f6c99ef1d2b0192b8075191" }] diff --git a/test/corpus/diff-summaries/javascript/math-operator.json b/test/corpus/diff-summaries/javascript/math-operator.json index f97625053..5c498a74b 100644 --- a/test/corpus/diff-summaries/javascript/math-operator.json +++ b/test/corpus/diff-summaries/javascript/math-operator.json @@ -27,9 +27,9 @@ "filePaths": [ "math-operator.js" ], - "sha1": "31ae73e147d1cd8cf95cfdf871344f18fdc91fa2", + "sha1": "29d3dd029a42aa320f2d154af468cc33e9fc7be2", "gitDir": "test/corpus/repos/javascript", - "sha2": "f8be46c403f576d3c18c1f3815f7480443755610" + "sha2": "3bcee56c9f08e47e37624d7961b7459e341435f7" } ,{ "testCaseDescription": "javascript-math-operator-replacement-insert-test", @@ -77,9 +77,9 @@ "filePaths": [ "math-operator.js" ], - "sha1": "f8be46c403f576d3c18c1f3815f7480443755610", + "sha1": "3bcee56c9f08e47e37624d7961b7459e341435f7", "gitDir": "test/corpus/repos/javascript", - "sha2": "2e407188cd18f565b68b11613a8dce6cb8400b1a" + "sha2": "d5ac4c9c8fa386bf983b962f242ff6eec966310b" } ,{ "testCaseDescription": "javascript-math-operator-delete-insert-test", @@ -153,9 +153,9 @@ "filePaths": [ "math-operator.js" ], - "sha1": "2e407188cd18f565b68b11613a8dce6cb8400b1a", + "sha1": "d5ac4c9c8fa386bf983b962f242ff6eec966310b", "gitDir": "test/corpus/repos/javascript", - "sha2": "80659409cc4250f823846584dc62802c9a1e6c01" + "sha2": "1ac0e212164f2068e691c5a1ee4d84af9b6a7b5a" } ,{ "testCaseDescription": "javascript-math-operator-replacement-test", @@ -229,9 +229,9 @@ "filePaths": [ "math-operator.js" ], - "sha1": "80659409cc4250f823846584dc62802c9a1e6c01", + "sha1": "1ac0e212164f2068e691c5a1ee4d84af9b6a7b5a", "gitDir": "test/corpus/repos/javascript", - "sha2": "f1878a2a74738ad67fb08d40334f351d4238e023" + "sha2": "be4676f35933afc323b26da0d809b21731d14733" } ,{ "testCaseDescription": "javascript-math-operator-delete-replacement-test", @@ -296,9 +296,9 @@ "filePaths": [ "math-operator.js" ], - "sha1": "f1878a2a74738ad67fb08d40334f351d4238e023", + "sha1": "be4676f35933afc323b26da0d809b21731d14733", "gitDir": "test/corpus/repos/javascript", - "sha2": "2eb48e213a12b09d764a5f58eec7d90985a9c66c" + "sha2": "5d632a1a0a0356c0301d21065697fc877a75b60c" } ,{ "testCaseDescription": "javascript-math-operator-delete-test", @@ -329,9 +329,9 @@ "filePaths": [ "math-operator.js" ], - "sha1": "2eb48e213a12b09d764a5f58eec7d90985a9c66c", + "sha1": "5d632a1a0a0356c0301d21065697fc877a75b60c", "gitDir": "test/corpus/repos/javascript", - "sha2": "e653a346a34e6374ab80a527dbbb777ec05f986c" + "sha2": "bbbfb139a7357fa00181518d13609396add9d3f7" } ,{ "testCaseDescription": "javascript-math-operator-delete-rest-test", @@ -362,7 +362,7 @@ "filePaths": [ "math-operator.js" ], - "sha1": "e653a346a34e6374ab80a527dbbb777ec05f986c", + "sha1": "bbbfb139a7357fa00181518d13609396add9d3f7", "gitDir": "test/corpus/repos/javascript", - "sha2": "cb37f95870629005756c374dade2599850dc09d3" + "sha2": "d8ca022a316c97349395e113ee5563dbfc64a120" }] diff --git a/test/corpus/diff-summaries/javascript/member-access-assignment.json b/test/corpus/diff-summaries/javascript/member-access-assignment.json index 35333c4b5..89af555b3 100644 --- a/test/corpus/diff-summaries/javascript/member-access-assignment.json +++ b/test/corpus/diff-summaries/javascript/member-access-assignment.json @@ -27,9 +27,9 @@ "filePaths": [ "member-access-assignment.js" ], - "sha1": "6882106e2e1564145c50f664a6446f6c37b1ab3f", + "sha1": "a8610d7d0057162d3dbbb845175a0fc8d993e0d6", "gitDir": "test/corpus/repos/javascript", - "sha2": "e25f5c9031b1c4881133070ab71fd755d165ead5" + "sha2": "08bbe0c2c7b34af221387f7b6e338937343d1ff7" } ,{ "testCaseDescription": "javascript-member-access-assignment-replacement-insert-test", @@ -77,9 +77,9 @@ "filePaths": [ "member-access-assignment.js" ], - "sha1": "e25f5c9031b1c4881133070ab71fd755d165ead5", + "sha1": "08bbe0c2c7b34af221387f7b6e338937343d1ff7", "gitDir": "test/corpus/repos/javascript", - "sha2": "9d9f04beab9f8d927ddbf0d4939d5651055d1577" + "sha2": "40cd1385fc2decff798fadd84b828eeffa386527" } ,{ "testCaseDescription": "javascript-member-access-assignment-delete-insert-test", @@ -123,9 +123,9 @@ "filePaths": [ "member-access-assignment.js" ], - "sha1": "9d9f04beab9f8d927ddbf0d4939d5651055d1577", + "sha1": "40cd1385fc2decff798fadd84b828eeffa386527", "gitDir": "test/corpus/repos/javascript", - "sha2": "bb31011c60ec572395dbe73bb48dd13be1cd6bb3" + "sha2": "2e8e5c2446be9ce6284d1e43510bcf30f6be19dc" } ,{ "testCaseDescription": "javascript-member-access-assignment-replacement-test", @@ -169,9 +169,9 @@ "filePaths": [ "member-access-assignment.js" ], - "sha1": "bb31011c60ec572395dbe73bb48dd13be1cd6bb3", + "sha1": "2e8e5c2446be9ce6284d1e43510bcf30f6be19dc", "gitDir": "test/corpus/repos/javascript", - "sha2": "7706b38694acad8dd246351a7623409cf63685ae" + "sha2": "ec1d0b50ba901bb9822226a0d615ff21d49de114" } ,{ "testCaseDescription": "javascript-member-access-assignment-delete-replacement-test", @@ -236,9 +236,9 @@ "filePaths": [ "member-access-assignment.js" ], - "sha1": "7706b38694acad8dd246351a7623409cf63685ae", + "sha1": "ec1d0b50ba901bb9822226a0d615ff21d49de114", "gitDir": "test/corpus/repos/javascript", - "sha2": "75dcf600f84cc516ba6e606ae623217e558da992" + "sha2": "8240cb6b7516b74de51980e453497e3595b4e628" } ,{ "testCaseDescription": "javascript-member-access-assignment-delete-test", @@ -269,9 +269,9 @@ "filePaths": [ "member-access-assignment.js" ], - "sha1": "75dcf600f84cc516ba6e606ae623217e558da992", + "sha1": "8240cb6b7516b74de51980e453497e3595b4e628", "gitDir": "test/corpus/repos/javascript", - "sha2": "003aa769197d4440824e267b4cc77c0f57a73561" + "sha2": "673b347c3edaa6ebd6922c7a383f39de4484aaee" } ,{ "testCaseDescription": "javascript-member-access-assignment-delete-rest-test", @@ -302,7 +302,7 @@ "filePaths": [ "member-access-assignment.js" ], - "sha1": "003aa769197d4440824e267b4cc77c0f57a73561", + "sha1": "673b347c3edaa6ebd6922c7a383f39de4484aaee", "gitDir": "test/corpus/repos/javascript", - "sha2": "9b3e79687880bf10eac28404f1b0de7e74e0ba44" + "sha2": "2777fc53b2f1b0e54aead0a015db9970af0795fe" }] diff --git a/test/corpus/diff-summaries/javascript/member-access.json b/test/corpus/diff-summaries/javascript/member-access.json index 9983d56f3..15479c963 100644 --- a/test/corpus/diff-summaries/javascript/member-access.json +++ b/test/corpus/diff-summaries/javascript/member-access.json @@ -27,9 +27,9 @@ "filePaths": [ "member-access.js" ], - "sha1": "fac60fda4353135fc163df6a61e7caff13930fc7", + "sha1": "0823b029fb4c9f6bd2d8197f3f0682bc2ddd5445", "gitDir": "test/corpus/repos/javascript", - "sha2": "b850815e1453fa74ddb093149a5dfef236567c8d" + "sha2": "99eb938a82f85d8d01ca67c2675efa387879d9ae" } ,{ "testCaseDescription": "javascript-member-access-replacement-insert-test", @@ -77,9 +77,9 @@ "filePaths": [ "member-access.js" ], - "sha1": "b850815e1453fa74ddb093149a5dfef236567c8d", + "sha1": "99eb938a82f85d8d01ca67c2675efa387879d9ae", "gitDir": "test/corpus/repos/javascript", - "sha2": "3a70c4b8bb055fd5a22da6919300d8f980d02a6c" + "sha2": "66971fc9cba9ba2a68c662baf8b83c1e678d5d4a" } ,{ "testCaseDescription": "javascript-member-access-delete-insert-test", @@ -123,9 +123,9 @@ "filePaths": [ "member-access.js" ], - "sha1": "3a70c4b8bb055fd5a22da6919300d8f980d02a6c", + "sha1": "66971fc9cba9ba2a68c662baf8b83c1e678d5d4a", "gitDir": "test/corpus/repos/javascript", - "sha2": "f60cc2bbbedaacb8eb700f1a3bda7b06275a8d27" + "sha2": "8bc32ef87162c91be8a015740a839c006f813127" } ,{ "testCaseDescription": "javascript-member-access-replacement-test", @@ -169,9 +169,9 @@ "filePaths": [ "member-access.js" ], - "sha1": "f60cc2bbbedaacb8eb700f1a3bda7b06275a8d27", + "sha1": "8bc32ef87162c91be8a015740a839c006f813127", "gitDir": "test/corpus/repos/javascript", - "sha2": "0663adbbe511b93eda40866fe376618cae48678d" + "sha2": "b646e69ee5a6aed13e920ab08dc34933210537fd" } ,{ "testCaseDescription": "javascript-member-access-delete-replacement-test", @@ -236,9 +236,9 @@ "filePaths": [ "member-access.js" ], - "sha1": "0663adbbe511b93eda40866fe376618cae48678d", + "sha1": "b646e69ee5a6aed13e920ab08dc34933210537fd", "gitDir": "test/corpus/repos/javascript", - "sha2": "837649081bbf641849fbc2d53224894bd8678f0b" + "sha2": "bd8074a2d66c30b37c6a657fbe3407e9bd32fa04" } ,{ "testCaseDescription": "javascript-member-access-delete-test", @@ -269,9 +269,9 @@ "filePaths": [ "member-access.js" ], - "sha1": "837649081bbf641849fbc2d53224894bd8678f0b", + "sha1": "bd8074a2d66c30b37c6a657fbe3407e9bd32fa04", "gitDir": "test/corpus/repos/javascript", - "sha2": "34eac603f132671867cb2457bb017ee2583a1d54" + "sha2": "58d7f9d9d4d795422a7c8abdae93fdf74dddaf31" } ,{ "testCaseDescription": "javascript-member-access-delete-rest-test", @@ -302,7 +302,7 @@ "filePaths": [ "member-access.js" ], - "sha1": "34eac603f132671867cb2457bb017ee2583a1d54", + "sha1": "58d7f9d9d4d795422a7c8abdae93fdf74dddaf31", "gitDir": "test/corpus/repos/javascript", - "sha2": "c11043ad084bd837ff463621da19892d2cc68719" + "sha2": "0c9b3b84cb49951e79891dae24edfddccbf579a1" }] diff --git a/test/corpus/diff-summaries/javascript/method-call.json b/test/corpus/diff-summaries/javascript/method-call.json index c36706a75..75752c492 100644 --- a/test/corpus/diff-summaries/javascript/method-call.json +++ b/test/corpus/diff-summaries/javascript/method-call.json @@ -27,9 +27,9 @@ "filePaths": [ "method-call.js" ], - "sha1": "bde44008cfb326f395ddb1071a073fc1113ffb3d", + "sha1": "ec567b366ed73c0a2d60e9e3a7736db883537a4c", "gitDir": "test/corpus/repos/javascript", - "sha2": "80d9e1c3f364424fd85eb3ee59e8790187596cba" + "sha2": "840b4603bd70e3aeb19603964bb4087442882b18" } ,{ "testCaseDescription": "javascript-method-call-replacement-insert-test", @@ -77,9 +77,9 @@ "filePaths": [ "method-call.js" ], - "sha1": "80d9e1c3f364424fd85eb3ee59e8790187596cba", + "sha1": "840b4603bd70e3aeb19603964bb4087442882b18", "gitDir": "test/corpus/repos/javascript", - "sha2": "d3da8ea868cfb41cfd38f8264933c2b7271c7734" + "sha2": "1e74a8573a26c304e4bdc2e687a955b5ec7b4b9a" } ,{ "testCaseDescription": "javascript-method-call-delete-insert-test", @@ -123,9 +123,9 @@ "filePaths": [ "method-call.js" ], - "sha1": "d3da8ea868cfb41cfd38f8264933c2b7271c7734", + "sha1": "1e74a8573a26c304e4bdc2e687a955b5ec7b4b9a", "gitDir": "test/corpus/repos/javascript", - "sha2": "262dfb0009e74472f2064911509300f17714002d" + "sha2": "447fd2cf545ddb584f7923defe1659bcbf7b7457" } ,{ "testCaseDescription": "javascript-method-call-replacement-test", @@ -169,9 +169,9 @@ "filePaths": [ "method-call.js" ], - "sha1": "262dfb0009e74472f2064911509300f17714002d", + "sha1": "447fd2cf545ddb584f7923defe1659bcbf7b7457", "gitDir": "test/corpus/repos/javascript", - "sha2": "6be53135abf6f6b89c6111798030e91721826c59" + "sha2": "beb6a15d9dd99a6abe9a15360a9bf11c4cb0b62d" } ,{ "testCaseDescription": "javascript-method-call-delete-replacement-test", @@ -236,9 +236,9 @@ "filePaths": [ "method-call.js" ], - "sha1": "6be53135abf6f6b89c6111798030e91721826c59", + "sha1": "beb6a15d9dd99a6abe9a15360a9bf11c4cb0b62d", "gitDir": "test/corpus/repos/javascript", - "sha2": "ee8b6a26e5f54845b632bdbf0543d81b6da15700" + "sha2": "bb8bafd9ca71ecc00d4a2b17f4994eafcc4a02b6" } ,{ "testCaseDescription": "javascript-method-call-delete-test", @@ -269,9 +269,9 @@ "filePaths": [ "method-call.js" ], - "sha1": "ee8b6a26e5f54845b632bdbf0543d81b6da15700", + "sha1": "bb8bafd9ca71ecc00d4a2b17f4994eafcc4a02b6", "gitDir": "test/corpus/repos/javascript", - "sha2": "1129af20d307473ea4e2d4d577ea53c7bdaed636" + "sha2": "64c5036bb60d199c3d753f5fbc67c030597daf55" } ,{ "testCaseDescription": "javascript-method-call-delete-rest-test", @@ -302,7 +302,7 @@ "filePaths": [ "method-call.js" ], - "sha1": "1129af20d307473ea4e2d4d577ea53c7bdaed636", + "sha1": "64c5036bb60d199c3d753f5fbc67c030597daf55", "gitDir": "test/corpus/repos/javascript", - "sha2": "7a9cdc6c356ec1e7fe6e47c923898d3e2e6a32cc" + "sha2": "d40eaae205d67245d41875f45a6cd12cc1c6beee" }] diff --git a/test/corpus/diff-summaries/javascript/named-function.json b/test/corpus/diff-summaries/javascript/named-function.json index c03cd9f4f..a8478f7d7 100644 --- a/test/corpus/diff-summaries/javascript/named-function.json +++ b/test/corpus/diff-summaries/javascript/named-function.json @@ -27,9 +27,9 @@ "filePaths": [ "named-function.js" ], - "sha1": "5fe4477fe4c9d164946d8aaf8fe66f107b0901b4", + "sha1": "5921bfd9de54f2a9868741666cba1c6fb5c4487a", "gitDir": "test/corpus/repos/javascript", - "sha2": "c86bb45b4e0f5b90e2ea9a371df0026ac6b147ca" + "sha2": "ed8f5dca6d1d96ef2b296bd5df98404d1b66c897" } ,{ "testCaseDescription": "javascript-named-function-replacement-insert-test", @@ -77,9 +77,9 @@ "filePaths": [ "named-function.js" ], - "sha1": "c86bb45b4e0f5b90e2ea9a371df0026ac6b147ca", + "sha1": "ed8f5dca6d1d96ef2b296bd5df98404d1b66c897", "gitDir": "test/corpus/repos/javascript", - "sha2": "370e7dcd8b0e49fa442f84396ad081ec1e61657e" + "sha2": "4222bcfe67238cc7af44c45f6ec0a142cfa17c67" } ,{ "testCaseDescription": "javascript-named-function-delete-insert-test", @@ -191,9 +191,9 @@ "filePaths": [ "named-function.js" ], - "sha1": "370e7dcd8b0e49fa442f84396ad081ec1e61657e", + "sha1": "4222bcfe67238cc7af44c45f6ec0a142cfa17c67", "gitDir": "test/corpus/repos/javascript", - "sha2": "3f231c35b4a10a3e3e2188bc377e56d1de4d67ca" + "sha2": "bc86a7cba72eea905c0d8c44adb3b4486b0a6a82" } ,{ "testCaseDescription": "javascript-named-function-replacement-test", @@ -305,9 +305,9 @@ "filePaths": [ "named-function.js" ], - "sha1": "3f231c35b4a10a3e3e2188bc377e56d1de4d67ca", + "sha1": "bc86a7cba72eea905c0d8c44adb3b4486b0a6a82", "gitDir": "test/corpus/repos/javascript", - "sha2": "f51128e06754269e3518efb3c37bfb93dde1e6e3" + "sha2": "f966010b747f91901e7aa9baad0cc7f1b6eef9ef" } ,{ "testCaseDescription": "javascript-named-function-delete-replacement-test", @@ -372,9 +372,9 @@ "filePaths": [ "named-function.js" ], - "sha1": "f51128e06754269e3518efb3c37bfb93dde1e6e3", + "sha1": "f966010b747f91901e7aa9baad0cc7f1b6eef9ef", "gitDir": "test/corpus/repos/javascript", - "sha2": "79a5f19ec8642f46ea2c6525df20c26fd2ca9cfc" + "sha2": "67fb491a47d084d91c43b668088e5dca89cc8a75" } ,{ "testCaseDescription": "javascript-named-function-delete-test", @@ -405,9 +405,9 @@ "filePaths": [ "named-function.js" ], - "sha1": "79a5f19ec8642f46ea2c6525df20c26fd2ca9cfc", + "sha1": "67fb491a47d084d91c43b668088e5dca89cc8a75", "gitDir": "test/corpus/repos/javascript", - "sha2": "1e9c6be37ab1267bf448d0475d8db90a8e60afd1" + "sha2": "d069d29ec02721e8951777c1a746b9717e2a0385" } ,{ "testCaseDescription": "javascript-named-function-delete-rest-test", @@ -438,7 +438,7 @@ "filePaths": [ "named-function.js" ], - "sha1": "1e9c6be37ab1267bf448d0475d8db90a8e60afd1", + "sha1": "d069d29ec02721e8951777c1a746b9717e2a0385", "gitDir": "test/corpus/repos/javascript", - "sha2": "fac60fda4353135fc163df6a61e7caff13930fc7" + "sha2": "0823b029fb4c9f6bd2d8197f3f0682bc2ddd5445" }] diff --git a/test/corpus/diff-summaries/javascript/nested-functions.json b/test/corpus/diff-summaries/javascript/nested-functions.json index 8f8b95b35..74984efaf 100644 --- a/test/corpus/diff-summaries/javascript/nested-functions.json +++ b/test/corpus/diff-summaries/javascript/nested-functions.json @@ -27,9 +27,9 @@ "filePaths": [ "nested-functions.js" ], - "sha1": "1ad3455503bfb6621a6b418f015349c2bd2a957d", + "sha1": "0ce3d1634f59a931d031cceac08ce3ea5e009bcd", "gitDir": "test/corpus/repos/javascript", - "sha2": "a895199ca338b56967e3a62869616c333b677551" + "sha2": "d29340565d945f1a5a9cb195bfe11aab2317b02a" } ,{ "testCaseDescription": "javascript-nested-functions-replacement-insert-test", @@ -77,9 +77,9 @@ "filePaths": [ "nested-functions.js" ], - "sha1": "a895199ca338b56967e3a62869616c333b677551", + "sha1": "d29340565d945f1a5a9cb195bfe11aab2317b02a", "gitDir": "test/corpus/repos/javascript", - "sha2": "801ab172957b72d8babcda5c151b009325b97d46" + "sha2": "f7bb7dcc5b7bb4d19e1e26ae694af81a2b6abab3" } ,{ "testCaseDescription": "javascript-nested-functions-delete-insert-test", @@ -153,9 +153,9 @@ "filePaths": [ "nested-functions.js" ], - "sha1": "801ab172957b72d8babcda5c151b009325b97d46", + "sha1": "f7bb7dcc5b7bb4d19e1e26ae694af81a2b6abab3", "gitDir": "test/corpus/repos/javascript", - "sha2": "e8b1e1efe706cf565df615f0cd9cc3514881ea82" + "sha2": "f7590f3a29efea3fa6955bc75a110c01ec134abe" } ,{ "testCaseDescription": "javascript-nested-functions-replacement-test", @@ -229,9 +229,9 @@ "filePaths": [ "nested-functions.js" ], - "sha1": "e8b1e1efe706cf565df615f0cd9cc3514881ea82", + "sha1": "f7590f3a29efea3fa6955bc75a110c01ec134abe", "gitDir": "test/corpus/repos/javascript", - "sha2": "50489ea764a308d499766e2c3e0da4215ce5ac34" + "sha2": "a5da6040b13da745bf4a8a2a33f66eded196cbde" } ,{ "testCaseDescription": "javascript-nested-functions-delete-replacement-test", @@ -296,9 +296,9 @@ "filePaths": [ "nested-functions.js" ], - "sha1": "50489ea764a308d499766e2c3e0da4215ce5ac34", + "sha1": "a5da6040b13da745bf4a8a2a33f66eded196cbde", "gitDir": "test/corpus/repos/javascript", - "sha2": "9d53457b894350de4b09b86914c8dbcc04f999ab" + "sha2": "0902cf79b0d1bf066d7703e6003aad6016ed93bd" } ,{ "testCaseDescription": "javascript-nested-functions-delete-test", @@ -329,9 +329,9 @@ "filePaths": [ "nested-functions.js" ], - "sha1": "9d53457b894350de4b09b86914c8dbcc04f999ab", + "sha1": "0902cf79b0d1bf066d7703e6003aad6016ed93bd", "gitDir": "test/corpus/repos/javascript", - "sha2": "4b43d1d5ce4632f57879d9021bae72e01ef78234" + "sha2": "8d9d2fc7a193f89c45f0589e241af82762344f9d" } ,{ "testCaseDescription": "javascript-nested-functions-delete-rest-test", @@ -362,7 +362,7 @@ "filePaths": [ "nested-functions.js" ], - "sha1": "4b43d1d5ce4632f57879d9021bae72e01ef78234", + "sha1": "8d9d2fc7a193f89c45f0589e241af82762344f9d", "gitDir": "test/corpus/repos/javascript", - "sha2": "6c18f0fbe80bb95f6642653913241b9065181591" + "sha2": "f8683054b3df6a44185993d0c11c1edcf4477b16" }] diff --git a/test/corpus/diff-summaries/javascript/null.json b/test/corpus/diff-summaries/javascript/null.json index 8290d24e2..f359c8c77 100644 --- a/test/corpus/diff-summaries/javascript/null.json +++ b/test/corpus/diff-summaries/javascript/null.json @@ -27,9 +27,9 @@ "filePaths": [ "null.js" ], - "sha1": "e876cda8f0a6a14bd8518d84e985c6616b2f5548", + "sha1": "5e6fd51739eb15db9fcd9e85e7f5c64da736056e", "gitDir": "test/corpus/repos/javascript", - "sha2": "7dcac4962ac6c1d7244fa02e89e11d3ea031fa94" + "sha2": "09d001185168db0f5777db8bbe8fdbc2317850f3" } ,{ "testCaseDescription": "javascript-null-replacement-insert-test", @@ -77,9 +77,9 @@ "filePaths": [ "null.js" ], - "sha1": "7dcac4962ac6c1d7244fa02e89e11d3ea031fa94", + "sha1": "09d001185168db0f5777db8bbe8fdbc2317850f3", "gitDir": "test/corpus/repos/javascript", - "sha2": "0562686e9fd41baa86ab32fbeb95bf53e9c55b61" + "sha2": "35e28a7dacfbe56dc784968b9a74dc237dc277a7" } ,{ "testCaseDescription": "javascript-null-delete-insert-test", @@ -127,9 +127,9 @@ "filePaths": [ "null.js" ], - "sha1": "0562686e9fd41baa86ab32fbeb95bf53e9c55b61", + "sha1": "35e28a7dacfbe56dc784968b9a74dc237dc277a7", "gitDir": "test/corpus/repos/javascript", - "sha2": "55c2830f73312678a37a376936a88e1c070a9400" + "sha2": "a8ddfdc834fb4cb46f918dd79169c0ba94039e28" } ,{ "testCaseDescription": "javascript-null-replacement-test", @@ -177,9 +177,9 @@ "filePaths": [ "null.js" ], - "sha1": "55c2830f73312678a37a376936a88e1c070a9400", + "sha1": "a8ddfdc834fb4cb46f918dd79169c0ba94039e28", "gitDir": "test/corpus/repos/javascript", - "sha2": "c950b4804d1bb4b66757d3d4684b3d3d07dd74ca" + "sha2": "a7e58f47ba6bbf42e87feafd33a924b9cb7b81a6" } ,{ "testCaseDescription": "javascript-null-delete-replacement-test", @@ -244,9 +244,9 @@ "filePaths": [ "null.js" ], - "sha1": "c950b4804d1bb4b66757d3d4684b3d3d07dd74ca", + "sha1": "a7e58f47ba6bbf42e87feafd33a924b9cb7b81a6", "gitDir": "test/corpus/repos/javascript", - "sha2": "5b41396ccd34ae1f6813fc4ab6ee6ec65877ae9d" + "sha2": "06a768142a69aa4d9537a4ff712fdd881d6dc58f" } ,{ "testCaseDescription": "javascript-null-delete-test", @@ -277,9 +277,9 @@ "filePaths": [ "null.js" ], - "sha1": "5b41396ccd34ae1f6813fc4ab6ee6ec65877ae9d", + "sha1": "06a768142a69aa4d9537a4ff712fdd881d6dc58f", "gitDir": "test/corpus/repos/javascript", - "sha2": "926763653ba7397bedb14c053ed3a3ca36df9de3" + "sha2": "e5d2ffd3ec75871b9f3a6af9a32b67d9c38bc198" } ,{ "testCaseDescription": "javascript-null-delete-rest-test", @@ -310,7 +310,7 @@ "filePaths": [ "null.js" ], - "sha1": "926763653ba7397bedb14c053ed3a3ca36df9de3", + "sha1": "e5d2ffd3ec75871b9f3a6af9a32b67d9c38bc198", "gitDir": "test/corpus/repos/javascript", - "sha2": "c4cbb6a4ff71852691d643f686d8231c9a3989a4" + "sha2": "0cf324666c04ffe5413f3e03ff09dc4a3883ab7c" }] diff --git a/test/corpus/diff-summaries/javascript/number.json b/test/corpus/diff-summaries/javascript/number.json index 1fae655a3..87e07ddad 100644 --- a/test/corpus/diff-summaries/javascript/number.json +++ b/test/corpus/diff-summaries/javascript/number.json @@ -27,9 +27,9 @@ "filePaths": [ "number.js" ], - "sha1": "20b94162d6be612a1c0111cb75ee0f3beadcab6e", + "sha1": "ca6f199fff7d76515b59c3e37344ea22225c3406", "gitDir": "test/corpus/repos/javascript", - "sha2": "1761ef1d335d09d579cbe1787558398e4f8d264b" + "sha2": "d15dd98056d0af5e286aca858a31ef433e6f9218" } ,{ "testCaseDescription": "javascript-number-replacement-insert-test", @@ -77,9 +77,9 @@ "filePaths": [ "number.js" ], - "sha1": "1761ef1d335d09d579cbe1787558398e4f8d264b", + "sha1": "d15dd98056d0af5e286aca858a31ef433e6f9218", "gitDir": "test/corpus/repos/javascript", - "sha2": "6196bff8f4104451020c72765217b3d224951070" + "sha2": "7f8fd62ebf444f3f84096aa3178029783c356279" } ,{ "testCaseDescription": "javascript-number-delete-insert-test", @@ -123,9 +123,9 @@ "filePaths": [ "number.js" ], - "sha1": "6196bff8f4104451020c72765217b3d224951070", + "sha1": "7f8fd62ebf444f3f84096aa3178029783c356279", "gitDir": "test/corpus/repos/javascript", - "sha2": "dc888e9f5129c85c17924e12d47538ae093853c0" + "sha2": "e057ec4e43f016f85bca7ecef40217f5b87cdb04" } ,{ "testCaseDescription": "javascript-number-replacement-test", @@ -169,9 +169,9 @@ "filePaths": [ "number.js" ], - "sha1": "dc888e9f5129c85c17924e12d47538ae093853c0", + "sha1": "e057ec4e43f016f85bca7ecef40217f5b87cdb04", "gitDir": "test/corpus/repos/javascript", - "sha2": "ee2939ca49b0baba42dd83ab0361e128c2565d93" + "sha2": "cccd069522c6d0d8d1b6b6313588d8a220089af9" } ,{ "testCaseDescription": "javascript-number-delete-replacement-test", @@ -236,9 +236,9 @@ "filePaths": [ "number.js" ], - "sha1": "ee2939ca49b0baba42dd83ab0361e128c2565d93", + "sha1": "cccd069522c6d0d8d1b6b6313588d8a220089af9", "gitDir": "test/corpus/repos/javascript", - "sha2": "b1fddfc7e3131549e7150bda348f9dddb963efc8" + "sha2": "e35f20ba047877b52fa927f58d2e661e6d4b038d" } ,{ "testCaseDescription": "javascript-number-delete-test", @@ -269,9 +269,9 @@ "filePaths": [ "number.js" ], - "sha1": "b1fddfc7e3131549e7150bda348f9dddb963efc8", + "sha1": "e35f20ba047877b52fa927f58d2e661e6d4b038d", "gitDir": "test/corpus/repos/javascript", - "sha2": "9bd4606cce2739f6d61c83c3b8045dbdf85874c3" + "sha2": "dd147ad548ac862d0191566bc6b706f0feb26a2c" } ,{ "testCaseDescription": "javascript-number-delete-rest-test", @@ -302,7 +302,7 @@ "filePaths": [ "number.js" ], - "sha1": "9bd4606cce2739f6d61c83c3b8045dbdf85874c3", + "sha1": "dd147ad548ac862d0191566bc6b706f0feb26a2c", "gitDir": "test/corpus/repos/javascript", - "sha2": "4df21e328803748f18b7cd64862f776a275b1448" + "sha2": "45a6d97047c9425f56128ec4e4400027be11cad7" }] diff --git a/test/corpus/diff-summaries/javascript/object-with-methods.json b/test/corpus/diff-summaries/javascript/object-with-methods.json index 4a09bfa0f..ec80c7d36 100644 --- a/test/corpus/diff-summaries/javascript/object-with-methods.json +++ b/test/corpus/diff-summaries/javascript/object-with-methods.json @@ -27,9 +27,9 @@ "filePaths": [ "objects-with-methods.js" ], - "sha1": "a7028eef7c56f7ba5c5dda0faadcfffe205d5a40", + "sha1": "96217c240d7773372a78d2a23601a4a97459fcad", "gitDir": "test/corpus/repos/javascript", - "sha2": "3006c2d8134eb46077d39614fdcb4521dbdb0b17" + "sha2": "6e0b9bd4f9e342ac6f9ec1d77b3fc530ae87a9a2" } ,{ "testCaseDescription": "javascript-objects-with-methods-replacement-insert-test", @@ -77,9 +77,9 @@ "filePaths": [ "objects-with-methods.js" ], - "sha1": "3006c2d8134eb46077d39614fdcb4521dbdb0b17", + "sha1": "6e0b9bd4f9e342ac6f9ec1d77b3fc530ae87a9a2", "gitDir": "test/corpus/repos/javascript", - "sha2": "8c983c007eb95af974dfe614c7d1d00e09518f71" + "sha2": "20ddbd693493a945428ab017ad8562bebecc19eb" } ,{ "testCaseDescription": "javascript-objects-with-methods-delete-insert-test", @@ -123,9 +123,9 @@ "filePaths": [ "objects-with-methods.js" ], - "sha1": "8c983c007eb95af974dfe614c7d1d00e09518f71", + "sha1": "20ddbd693493a945428ab017ad8562bebecc19eb", "gitDir": "test/corpus/repos/javascript", - "sha2": "55dcede10e26e4cf3b859b592a42217948b92144" + "sha2": "e912fc9f4f009ec09d1c5cc288beea94f9b13de0" } ,{ "testCaseDescription": "javascript-objects-with-methods-replacement-test", @@ -169,9 +169,9 @@ "filePaths": [ "objects-with-methods.js" ], - "sha1": "55dcede10e26e4cf3b859b592a42217948b92144", + "sha1": "e912fc9f4f009ec09d1c5cc288beea94f9b13de0", "gitDir": "test/corpus/repos/javascript", - "sha2": "e2d692987dd8c6a20ac236a754dff49468cc37ef" + "sha2": "62fdf99216ad8608e9371c76c05b1e4e5c5574d5" } ,{ "testCaseDescription": "javascript-objects-with-methods-delete-replacement-test", @@ -236,9 +236,9 @@ "filePaths": [ "objects-with-methods.js" ], - "sha1": "e2d692987dd8c6a20ac236a754dff49468cc37ef", + "sha1": "62fdf99216ad8608e9371c76c05b1e4e5c5574d5", "gitDir": "test/corpus/repos/javascript", - "sha2": "96aea9adf4dd98dad9f18a880cc77865485780b7" + "sha2": "48db8be531ea86fab4d79cddcc9378bbc0e26085" } ,{ "testCaseDescription": "javascript-objects-with-methods-delete-test", @@ -269,9 +269,9 @@ "filePaths": [ "objects-with-methods.js" ], - "sha1": "96aea9adf4dd98dad9f18a880cc77865485780b7", + "sha1": "48db8be531ea86fab4d79cddcc9378bbc0e26085", "gitDir": "test/corpus/repos/javascript", - "sha2": "4f77fa590f5ec5abbe9af2cdf0e933c1f7930dbb" + "sha2": "67c7dde79edbfb3e52f0941c20215412fe63df35" } ,{ "testCaseDescription": "javascript-objects-with-methods-delete-rest-test", @@ -302,7 +302,7 @@ "filePaths": [ "objects-with-methods.js" ], - "sha1": "4f77fa590f5ec5abbe9af2cdf0e933c1f7930dbb", + "sha1": "67c7dde79edbfb3e52f0941c20215412fe63df35", "gitDir": "test/corpus/repos/javascript", - "sha2": "b2c18e39f6754f6fbc0ce238ea24ee7386d7b34f" + "sha2": "c889f65f6a973b3a266eb413d25af2589ac90aad" }] diff --git a/test/corpus/diff-summaries/javascript/object.json b/test/corpus/diff-summaries/javascript/object.json index 294c78ddd..66924c77e 100644 --- a/test/corpus/diff-summaries/javascript/object.json +++ b/test/corpus/diff-summaries/javascript/object.json @@ -27,9 +27,9 @@ "filePaths": [ "object.js" ], - "sha1": "05cde689481d4a3150edf8d68c07b711548b1c42", + "sha1": "25d0dca67cfd26a4d408ec7cc751b428dd7d0451", "gitDir": "test/corpus/repos/javascript", - "sha2": "a82d05e8e33ae0b96a558c5e83a4c2df6de327cc" + "sha2": "7f5cbbc47228c1104892eada850c44c6882f2e75" } ,{ "testCaseDescription": "javascript-object-replacement-insert-test", @@ -77,9 +77,9 @@ "filePaths": [ "object.js" ], - "sha1": "a82d05e8e33ae0b96a558c5e83a4c2df6de327cc", + "sha1": "7f5cbbc47228c1104892eada850c44c6882f2e75", "gitDir": "test/corpus/repos/javascript", - "sha2": "6da3ab8b36cd94063af7d79dac0d1fc3681f70cd" + "sha2": "af8e715d412674a9e461911257f6cf7300181ecf" } ,{ "testCaseDescription": "javascript-object-delete-insert-test", @@ -127,9 +127,9 @@ "filePaths": [ "object.js" ], - "sha1": "6da3ab8b36cd94063af7d79dac0d1fc3681f70cd", + "sha1": "af8e715d412674a9e461911257f6cf7300181ecf", "gitDir": "test/corpus/repos/javascript", - "sha2": "1324b314637c3121330a2eb556e01c812056edab" + "sha2": "de0bf64501649b87dfa7c4cb899f7d3b10e0aeb2" } ,{ "testCaseDescription": "javascript-object-replacement-test", @@ -177,9 +177,9 @@ "filePaths": [ "object.js" ], - "sha1": "1324b314637c3121330a2eb556e01c812056edab", + "sha1": "de0bf64501649b87dfa7c4cb899f7d3b10e0aeb2", "gitDir": "test/corpus/repos/javascript", - "sha2": "ac121256df1e9fe9f2d385aa0410250763c35798" + "sha2": "1edcda3336c0e559ed414893984424a0a3933d46" } ,{ "testCaseDescription": "javascript-object-delete-replacement-test", @@ -244,9 +244,9 @@ "filePaths": [ "object.js" ], - "sha1": "ac121256df1e9fe9f2d385aa0410250763c35798", + "sha1": "1edcda3336c0e559ed414893984424a0a3933d46", "gitDir": "test/corpus/repos/javascript", - "sha2": "22387f65f861db2c90f8e89e3035c436f9013523" + "sha2": "876287a27a2dd4a49bc577d774257cea7c86f22d" } ,{ "testCaseDescription": "javascript-object-delete-test", @@ -277,9 +277,9 @@ "filePaths": [ "object.js" ], - "sha1": "22387f65f861db2c90f8e89e3035c436f9013523", + "sha1": "876287a27a2dd4a49bc577d774257cea7c86f22d", "gitDir": "test/corpus/repos/javascript", - "sha2": "b602e503004cc504fc1368fe867cbdc673940e91" + "sha2": "0186f0d7bd20043d83475e7c5f601ab06c156246" } ,{ "testCaseDescription": "javascript-object-delete-rest-test", @@ -310,7 +310,7 @@ "filePaths": [ "object.js" ], - "sha1": "b602e503004cc504fc1368fe867cbdc673940e91", + "sha1": "0186f0d7bd20043d83475e7c5f601ab06c156246", "gitDir": "test/corpus/repos/javascript", - "sha2": "a0404e9e7b61466d953a033ff444c10691cea549" + "sha2": "2f014a3eddb509376944a4938ace7c0eb952308d" }] diff --git a/test/corpus/diff-summaries/javascript/regex.json b/test/corpus/diff-summaries/javascript/regex.json index f2a1c919e..6f486f11c 100644 --- a/test/corpus/diff-summaries/javascript/regex.json +++ b/test/corpus/diff-summaries/javascript/regex.json @@ -27,9 +27,9 @@ "filePaths": [ "regex.js" ], - "sha1": "0578f24cf85fce35bd787e60e1b210b79f462858", + "sha1": "a23b0a588d860380edd5b815810c34e35d5855a8", "gitDir": "test/corpus/repos/javascript", - "sha2": "f58477ae790a5642d28917f80ce0eef50d3942f8" + "sha2": "217e36b213c91a65d77f46926fcb534902df7e19" } ,{ "testCaseDescription": "javascript-regex-replacement-insert-test", @@ -77,9 +77,9 @@ "filePaths": [ "regex.js" ], - "sha1": "f58477ae790a5642d28917f80ce0eef50d3942f8", + "sha1": "217e36b213c91a65d77f46926fcb534902df7e19", "gitDir": "test/corpus/repos/javascript", - "sha2": "2a69523d4cbd85210fb91e34d2e3d780edadb84a" + "sha2": "4a52d9e2ec880aa7188150f006b90c8917423bd4" } ,{ "testCaseDescription": "javascript-regex-delete-insert-test", @@ -123,9 +123,9 @@ "filePaths": [ "regex.js" ], - "sha1": "2a69523d4cbd85210fb91e34d2e3d780edadb84a", + "sha1": "4a52d9e2ec880aa7188150f006b90c8917423bd4", "gitDir": "test/corpus/repos/javascript", - "sha2": "0db3f4dd27fec529d440a8e90b5f163017d6d1e8" + "sha2": "f59bede5c9d87962f3ccd92e92b8033b62df42d6" } ,{ "testCaseDescription": "javascript-regex-replacement-test", @@ -169,9 +169,9 @@ "filePaths": [ "regex.js" ], - "sha1": "0db3f4dd27fec529d440a8e90b5f163017d6d1e8", + "sha1": "f59bede5c9d87962f3ccd92e92b8033b62df42d6", "gitDir": "test/corpus/repos/javascript", - "sha2": "dfb43e551c9e2376cf3b7de60e4ab10aa24a1cd1" + "sha2": "fd2e9c9a9fc22df2f9d419ca900cd31829009900" } ,{ "testCaseDescription": "javascript-regex-delete-replacement-test", @@ -236,9 +236,9 @@ "filePaths": [ "regex.js" ], - "sha1": "dfb43e551c9e2376cf3b7de60e4ab10aa24a1cd1", + "sha1": "fd2e9c9a9fc22df2f9d419ca900cd31829009900", "gitDir": "test/corpus/repos/javascript", - "sha2": "a6a36758433fd19118cd451bc078fff428925b0f" + "sha2": "f1bb99be7d4da0912f1a327169283becd330cee2" } ,{ "testCaseDescription": "javascript-regex-delete-test", @@ -269,9 +269,9 @@ "filePaths": [ "regex.js" ], - "sha1": "a6a36758433fd19118cd451bc078fff428925b0f", + "sha1": "f1bb99be7d4da0912f1a327169283becd330cee2", "gitDir": "test/corpus/repos/javascript", - "sha2": "098252dc18d9aad40432ffc927069d1a61e76ce9" + "sha2": "7f501f49c0f89042f4f95f6a52e1a984fe76176a" } ,{ "testCaseDescription": "javascript-regex-delete-rest-test", @@ -302,7 +302,7 @@ "filePaths": [ "regex.js" ], - "sha1": "098252dc18d9aad40432ffc927069d1a61e76ce9", + "sha1": "7f501f49c0f89042f4f95f6a52e1a984fe76176a", "gitDir": "test/corpus/repos/javascript", - "sha2": "1fbd44cbdd925bb727f5b07af974a37db31b3ea0" + "sha2": "f4a276fc53b44233f1996fab1c4310602ddc195f" }] diff --git a/test/corpus/diff-summaries/javascript/relational-operator.json b/test/corpus/diff-summaries/javascript/relational-operator.json index 73443a696..9795d09af 100644 --- a/test/corpus/diff-summaries/javascript/relational-operator.json +++ b/test/corpus/diff-summaries/javascript/relational-operator.json @@ -27,9 +27,9 @@ "filePaths": [ "relational-operator.js" ], - "sha1": "4a348bc66ccc50e501fe3e49df1cd797d99ca405", + "sha1": "0d4682971dbf0345afd2593f1068dc25c4cd0e84", "gitDir": "test/corpus/repos/javascript", - "sha2": "ddbb70b6d30615c62f926c6e5f3b9868d8102c2b" + "sha2": "effcf61b37fbba12b7e8b2c9c987cf33c2814eb5" } ,{ "testCaseDescription": "javascript-relational-operator-replacement-insert-test", @@ -77,9 +77,9 @@ "filePaths": [ "relational-operator.js" ], - "sha1": "ddbb70b6d30615c62f926c6e5f3b9868d8102c2b", + "sha1": "effcf61b37fbba12b7e8b2c9c987cf33c2814eb5", "gitDir": "test/corpus/repos/javascript", - "sha2": "e3b836e0a0b0ece117db55b8a9e4f5042fbe994a" + "sha2": "689679d7cbce619b3cebc7a5492e6ccbe1cb7f5a" } ,{ "testCaseDescription": "javascript-relational-operator-delete-insert-test", @@ -90,9 +90,9 @@ "filePaths": [ "relational-operator.js" ], - "sha1": "e3b836e0a0b0ece117db55b8a9e4f5042fbe994a", + "sha1": "689679d7cbce619b3cebc7a5492e6ccbe1cb7f5a", "gitDir": "test/corpus/repos/javascript", - "sha2": "cecfdf6d66df9ae0c0002d04925f509d2cf27fd7" + "sha2": "88f87130aa4119c6be38c89cfa33f76a31ed1924" } ,{ "testCaseDescription": "javascript-relational-operator-replacement-test", @@ -103,9 +103,9 @@ "filePaths": [ "relational-operator.js" ], - "sha1": "cecfdf6d66df9ae0c0002d04925f509d2cf27fd7", + "sha1": "88f87130aa4119c6be38c89cfa33f76a31ed1924", "gitDir": "test/corpus/repos/javascript", - "sha2": "9ac444b7e34c82e6280aac2751be6e1b2f7aa2e3" + "sha2": "0e932c3e06f7ab7e22bccd7b27d0dd90a459709e" } ,{ "testCaseDescription": "javascript-relational-operator-delete-replacement-test", @@ -136,9 +136,9 @@ "filePaths": [ "relational-operator.js" ], - "sha1": "9ac444b7e34c82e6280aac2751be6e1b2f7aa2e3", + "sha1": "0e932c3e06f7ab7e22bccd7b27d0dd90a459709e", "gitDir": "test/corpus/repos/javascript", - "sha2": "9eea04a227ce9e4647d462615e7d72109ceb2bd1" + "sha2": "0c735369dcf138f48d54d653d9d6f6b54c6152a4" } ,{ "testCaseDescription": "javascript-relational-operator-delete-test", @@ -169,9 +169,9 @@ "filePaths": [ "relational-operator.js" ], - "sha1": "9eea04a227ce9e4647d462615e7d72109ceb2bd1", + "sha1": "0c735369dcf138f48d54d653d9d6f6b54c6152a4", "gitDir": "test/corpus/repos/javascript", - "sha2": "1b50dad44a6ffa8b3bde53fdd4c3dd80ba19e849" + "sha2": "1f0c2c97efb56381e072d3abba5bb3d1739d39f1" } ,{ "testCaseDescription": "javascript-relational-operator-delete-rest-test", @@ -202,7 +202,7 @@ "filePaths": [ "relational-operator.js" ], - "sha1": "1b50dad44a6ffa8b3bde53fdd4c3dd80ba19e849", + "sha1": "1f0c2c97efb56381e072d3abba5bb3d1739d39f1", "gitDir": "test/corpus/repos/javascript", - "sha2": "8c6579c037e31738b4decb4405d7a17824524ca3" + "sha2": "b7399e257e9ce0b28ce3080ac7e8edb2778614a3" }] diff --git a/test/corpus/diff-summaries/javascript/return-statement.json b/test/corpus/diff-summaries/javascript/return-statement.json index bd06723a4..2b28975ec 100644 --- a/test/corpus/diff-summaries/javascript/return-statement.json +++ b/test/corpus/diff-summaries/javascript/return-statement.json @@ -27,9 +27,9 @@ "filePaths": [ "return-statement.js" ], - "sha1": "11ce49dc14d6c3b4c0baef54a2456d4bc667b992", + "sha1": "ea1cb608a188b06972bcdf47db341f8b953076b1", "gitDir": "test/corpus/repos/javascript", - "sha2": "c780ce189b53bd43241c7c278c5a7749dcc14d81" + "sha2": "d6d43126c146818136ee53240cc0710fa5d6d5dd" } ,{ "testCaseDescription": "javascript-return-statement-replacement-insert-test", @@ -77,9 +77,9 @@ "filePaths": [ "return-statement.js" ], - "sha1": "c780ce189b53bd43241c7c278c5a7749dcc14d81", + "sha1": "d6d43126c146818136ee53240cc0710fa5d6d5dd", "gitDir": "test/corpus/repos/javascript", - "sha2": "219a0207a0a6f7711dbc837e9cfb87a610f9df07" + "sha2": "66af3d2ede52997e1459b9982344eea628c78ec1" } ,{ "testCaseDescription": "javascript-return-statement-delete-insert-test", @@ -110,9 +110,9 @@ "filePaths": [ "return-statement.js" ], - "sha1": "219a0207a0a6f7711dbc837e9cfb87a610f9df07", + "sha1": "66af3d2ede52997e1459b9982344eea628c78ec1", "gitDir": "test/corpus/repos/javascript", - "sha2": "f48d1d569a04768182d8fd9d92854d2fbd106d16" + "sha2": "d69b3b6c2cf5dbbfe05929c9ccd38f9e70db044f" } ,{ "testCaseDescription": "javascript-return-statement-replacement-test", @@ -143,9 +143,9 @@ "filePaths": [ "return-statement.js" ], - "sha1": "f48d1d569a04768182d8fd9d92854d2fbd106d16", + "sha1": "d69b3b6c2cf5dbbfe05929c9ccd38f9e70db044f", "gitDir": "test/corpus/repos/javascript", - "sha2": "8955ee5588fdf2e27ac4ba5a20fcf4f2c3f812ed" + "sha2": "dc2e62f6d42b3b407e2f467005d0013c4d49d506" } ,{ "testCaseDescription": "javascript-return-statement-delete-replacement-test", @@ -210,9 +210,9 @@ "filePaths": [ "return-statement.js" ], - "sha1": "8955ee5588fdf2e27ac4ba5a20fcf4f2c3f812ed", + "sha1": "dc2e62f6d42b3b407e2f467005d0013c4d49d506", "gitDir": "test/corpus/repos/javascript", - "sha2": "8b92b202fe3a41f9f5ad570e273e5cca32320547" + "sha2": "0399b8e3ad0efd3c8c08b55e737025295e717c68" } ,{ "testCaseDescription": "javascript-return-statement-delete-test", @@ -243,9 +243,9 @@ "filePaths": [ "return-statement.js" ], - "sha1": "8b92b202fe3a41f9f5ad570e273e5cca32320547", + "sha1": "0399b8e3ad0efd3c8c08b55e737025295e717c68", "gitDir": "test/corpus/repos/javascript", - "sha2": "644db02de4b5f1d4d800d643c2638d2a126e235c" + "sha2": "46019b62030cdac776e7844c5e07901b0d2934d3" } ,{ "testCaseDescription": "javascript-return-statement-delete-rest-test", @@ -276,7 +276,7 @@ "filePaths": [ "return-statement.js" ], - "sha1": "644db02de4b5f1d4d800d643c2638d2a126e235c", + "sha1": "46019b62030cdac776e7844c5e07901b0d2934d3", "gitDir": "test/corpus/repos/javascript", - "sha2": "9f1361ad761d81ff9d3b968ebeefa0f9640ae0ca" + "sha2": "b9adfaa1ed76ab8073a888953b9f52ed07ae901d" }] diff --git a/test/corpus/diff-summaries/javascript/string.json b/test/corpus/diff-summaries/javascript/string.json index f66a0804b..6438e4bee 100644 --- a/test/corpus/diff-summaries/javascript/string.json +++ b/test/corpus/diff-summaries/javascript/string.json @@ -27,9 +27,9 @@ "filePaths": [ "string.js" ], - "sha1": "b2c18e39f6754f6fbc0ce238ea24ee7386d7b34f", + "sha1": "c889f65f6a973b3a266eb413d25af2589ac90aad", "gitDir": "test/corpus/repos/javascript", - "sha2": "0f81035000f8efd0e62f121e0a643cc8354b9178" + "sha2": "821617bc632d99ebd1f9fd30b237096231b0e15d" } ,{ "testCaseDescription": "javascript-string-replacement-insert-test", @@ -77,9 +77,9 @@ "filePaths": [ "string.js" ], - "sha1": "0f81035000f8efd0e62f121e0a643cc8354b9178", + "sha1": "821617bc632d99ebd1f9fd30b237096231b0e15d", "gitDir": "test/corpus/repos/javascript", - "sha2": "35dd5365f89a59f05c68a1edb5284e33847c688e" + "sha2": "1e2dcdc8a9a18a7d337d93009fbe9658db462783" } ,{ "testCaseDescription": "javascript-string-delete-insert-test", @@ -123,9 +123,9 @@ "filePaths": [ "string.js" ], - "sha1": "35dd5365f89a59f05c68a1edb5284e33847c688e", + "sha1": "1e2dcdc8a9a18a7d337d93009fbe9658db462783", "gitDir": "test/corpus/repos/javascript", - "sha2": "1234962d618b026bc92ab9ab79641e9ec21b0cac" + "sha2": "b3db1e245fd2d0ad01e0e27460d6e97af1c564db" } ,{ "testCaseDescription": "javascript-string-replacement-test", @@ -169,9 +169,9 @@ "filePaths": [ "string.js" ], - "sha1": "1234962d618b026bc92ab9ab79641e9ec21b0cac", + "sha1": "b3db1e245fd2d0ad01e0e27460d6e97af1c564db", "gitDir": "test/corpus/repos/javascript", - "sha2": "25ff0717d0d1ec49b053a6d07e888d0e78585c35" + "sha2": "ca7fee05b34e388c9734c71b906655bcf6f01295" } ,{ "testCaseDescription": "javascript-string-delete-replacement-test", @@ -236,9 +236,9 @@ "filePaths": [ "string.js" ], - "sha1": "25ff0717d0d1ec49b053a6d07e888d0e78585c35", + "sha1": "ca7fee05b34e388c9734c71b906655bcf6f01295", "gitDir": "test/corpus/repos/javascript", - "sha2": "78d3c4d8e5f05bd6421f0eeeb952dc16d7855462" + "sha2": "293106e45dc93d792c0e410c81728e60e60dc090" } ,{ "testCaseDescription": "javascript-string-delete-test", @@ -269,9 +269,9 @@ "filePaths": [ "string.js" ], - "sha1": "78d3c4d8e5f05bd6421f0eeeb952dc16d7855462", + "sha1": "293106e45dc93d792c0e410c81728e60e60dc090", "gitDir": "test/corpus/repos/javascript", - "sha2": "c2fee245e107483bd5c60ab7b0de718e822fd93a" + "sha2": "4a11d9c2213843857f1f4eddf9c3980aaabcdeaa" } ,{ "testCaseDescription": "javascript-string-delete-rest-test", @@ -302,7 +302,7 @@ "filePaths": [ "string.js" ], - "sha1": "c2fee245e107483bd5c60ab7b0de718e822fd93a", + "sha1": "4a11d9c2213843857f1f4eddf9c3980aaabcdeaa", "gitDir": "test/corpus/repos/javascript", - "sha2": "20b94162d6be612a1c0111cb75ee0f3beadcab6e" + "sha2": "ca6f199fff7d76515b59c3e37344ea22225c3406" }] diff --git a/test/corpus/diff-summaries/javascript/subscript-access-assignment.json b/test/corpus/diff-summaries/javascript/subscript-access-assignment.json index 1aaf98f29..395bc60f7 100644 --- a/test/corpus/diff-summaries/javascript/subscript-access-assignment.json +++ b/test/corpus/diff-summaries/javascript/subscript-access-assignment.json @@ -27,9 +27,9 @@ "filePaths": [ "subscript-access-assignment.js" ], - "sha1": "9b3e79687880bf10eac28404f1b0de7e74e0ba44", + "sha1": "2777fc53b2f1b0e54aead0a015db9970af0795fe", "gitDir": "test/corpus/repos/javascript", - "sha2": "406fa823725f46c37168a5062f0fafdee1e5efff" + "sha2": "56d078c8be955e974b02bb9413e8196e0e092cdb" } ,{ "testCaseDescription": "javascript-subscript-access-assignment-replacement-insert-test", @@ -77,9 +77,9 @@ "filePaths": [ "subscript-access-assignment.js" ], - "sha1": "406fa823725f46c37168a5062f0fafdee1e5efff", + "sha1": "56d078c8be955e974b02bb9413e8196e0e092cdb", "gitDir": "test/corpus/repos/javascript", - "sha2": "12579d2ea4d43255f99a99bab55b6d84f4c545e8" + "sha2": "b6764107f971cb9f7ddf592f63c48d6e7920eb79" } ,{ "testCaseDescription": "javascript-subscript-access-assignment-delete-insert-test", @@ -123,9 +123,9 @@ "filePaths": [ "subscript-access-assignment.js" ], - "sha1": "12579d2ea4d43255f99a99bab55b6d84f4c545e8", + "sha1": "b6764107f971cb9f7ddf592f63c48d6e7920eb79", "gitDir": "test/corpus/repos/javascript", - "sha2": "b695f35574816f1726df991f9e8a5129b6c00dbd" + "sha2": "c6cf46d469bff2839ea43d397a672cfeefb7fed3" } ,{ "testCaseDescription": "javascript-subscript-access-assignment-replacement-test", @@ -169,9 +169,9 @@ "filePaths": [ "subscript-access-assignment.js" ], - "sha1": "b695f35574816f1726df991f9e8a5129b6c00dbd", + "sha1": "c6cf46d469bff2839ea43d397a672cfeefb7fed3", "gitDir": "test/corpus/repos/javascript", - "sha2": "2f092bfe85d05028172fe8c07380f7ee1c37aa3e" + "sha2": "be2f114b3b50c34e16eb2a9201b3b63ba6a08617" } ,{ "testCaseDescription": "javascript-subscript-access-assignment-delete-replacement-test", @@ -236,9 +236,9 @@ "filePaths": [ "subscript-access-assignment.js" ], - "sha1": "2f092bfe85d05028172fe8c07380f7ee1c37aa3e", + "sha1": "be2f114b3b50c34e16eb2a9201b3b63ba6a08617", "gitDir": "test/corpus/repos/javascript", - "sha2": "0d6c920c95f5cbbd159719a805758233c971cae8" + "sha2": "5ca3653b76f677ce067dc9c1509ab906f205cd1b" } ,{ "testCaseDescription": "javascript-subscript-access-assignment-delete-test", @@ -269,9 +269,9 @@ "filePaths": [ "subscript-access-assignment.js" ], - "sha1": "0d6c920c95f5cbbd159719a805758233c971cae8", + "sha1": "5ca3653b76f677ce067dc9c1509ab906f205cd1b", "gitDir": "test/corpus/repos/javascript", - "sha2": "015fb2b13539b87607f327118bc59c932adb151f" + "sha2": "5e1b3305c8e5ffeaffd2e5a040a07fe6e1965484" } ,{ "testCaseDescription": "javascript-subscript-access-assignment-delete-rest-test", @@ -302,7 +302,7 @@ "filePaths": [ "subscript-access-assignment.js" ], - "sha1": "015fb2b13539b87607f327118bc59c932adb151f", + "sha1": "5e1b3305c8e5ffeaffd2e5a040a07fe6e1965484", "gitDir": "test/corpus/repos/javascript", - "sha2": "25e371a5c0ef7434f562af7ca9a9bfab5a157932" + "sha2": "1cda03e29bc707037e0b55c899bc9d9fec1239db" }] diff --git a/test/corpus/diff-summaries/javascript/subscript-access-string.json b/test/corpus/diff-summaries/javascript/subscript-access-string.json index 4facb19bf..5d181b82c 100644 --- a/test/corpus/diff-summaries/javascript/subscript-access-string.json +++ b/test/corpus/diff-summaries/javascript/subscript-access-string.json @@ -27,9 +27,9 @@ "filePaths": [ "subscript-access-string.js" ], - "sha1": "cbebbe0cb3d24a7adb492b88b6b5769c9b895654", + "sha1": "7ae7a3452b9ea0561d469df9ecaf32e6eb2d9474", "gitDir": "test/corpus/repos/javascript", - "sha2": "b3cdd00f14a2880dee975305faf0a8268c700ca4" + "sha2": "5ff8e2661eac926dd7ed244797f9eada19ad7f5d" } ,{ "testCaseDescription": "javascript-subscript-access-string-replacement-insert-test", @@ -77,9 +77,9 @@ "filePaths": [ "subscript-access-string.js" ], - "sha1": "b3cdd00f14a2880dee975305faf0a8268c700ca4", + "sha1": "5ff8e2661eac926dd7ed244797f9eada19ad7f5d", "gitDir": "test/corpus/repos/javascript", - "sha2": "874fe50a89cdc77032efc2fb67e29ed8c3fbc66c" + "sha2": "9af8071731157d775318d5114e4dcac580f6f716" } ,{ "testCaseDescription": "javascript-subscript-access-string-delete-insert-test", @@ -123,9 +123,9 @@ "filePaths": [ "subscript-access-string.js" ], - "sha1": "874fe50a89cdc77032efc2fb67e29ed8c3fbc66c", + "sha1": "9af8071731157d775318d5114e4dcac580f6f716", "gitDir": "test/corpus/repos/javascript", - "sha2": "86756c297918a1e4812fb77db3970d43979df6cd" + "sha2": "eae6318d1c52e7127cc46aff2e75528ad361f57c" } ,{ "testCaseDescription": "javascript-subscript-access-string-replacement-test", @@ -169,9 +169,9 @@ "filePaths": [ "subscript-access-string.js" ], - "sha1": "86756c297918a1e4812fb77db3970d43979df6cd", + "sha1": "eae6318d1c52e7127cc46aff2e75528ad361f57c", "gitDir": "test/corpus/repos/javascript", - "sha2": "a536d6f573c0c3763b9dc6f4795362d33515ba6f" + "sha2": "58eaf98e9194b3d599455e7e5f250a420f82d155" } ,{ "testCaseDescription": "javascript-subscript-access-string-delete-replacement-test", @@ -236,9 +236,9 @@ "filePaths": [ "subscript-access-string.js" ], - "sha1": "a536d6f573c0c3763b9dc6f4795362d33515ba6f", + "sha1": "58eaf98e9194b3d599455e7e5f250a420f82d155", "gitDir": "test/corpus/repos/javascript", - "sha2": "e9eec0492107b1e1a88b908a99081ed82cd0ac71" + "sha2": "8474b084fdbea46f9d61c8f84a08a1b65312a389" } ,{ "testCaseDescription": "javascript-subscript-access-string-delete-test", @@ -269,9 +269,9 @@ "filePaths": [ "subscript-access-string.js" ], - "sha1": "e9eec0492107b1e1a88b908a99081ed82cd0ac71", + "sha1": "8474b084fdbea46f9d61c8f84a08a1b65312a389", "gitDir": "test/corpus/repos/javascript", - "sha2": "bd4c80248676d64aea1381b767de1d9db079caa1" + "sha2": "72743b4417df690550bad30298e5a3fcf7b72115" } ,{ "testCaseDescription": "javascript-subscript-access-string-delete-rest-test", @@ -302,7 +302,7 @@ "filePaths": [ "subscript-access-string.js" ], - "sha1": "bd4c80248676d64aea1381b767de1d9db079caa1", + "sha1": "72743b4417df690550bad30298e5a3fcf7b72115", "gitDir": "test/corpus/repos/javascript", - "sha2": "5172568a010252e98966d57a1c3fc1ade326f9ab" + "sha2": "6d2a9f7093c2227f7d7eeedabf694118f5f17c73" }] diff --git a/test/corpus/diff-summaries/javascript/subscript-access-variable.json b/test/corpus/diff-summaries/javascript/subscript-access-variable.json index ce75675d4..460b875c6 100644 --- a/test/corpus/diff-summaries/javascript/subscript-access-variable.json +++ b/test/corpus/diff-summaries/javascript/subscript-access-variable.json @@ -27,9 +27,9 @@ "filePaths": [ "subscript-access-variable.js" ], - "sha1": "c11043ad084bd837ff463621da19892d2cc68719", + "sha1": "0c9b3b84cb49951e79891dae24edfddccbf579a1", "gitDir": "test/corpus/repos/javascript", - "sha2": "a076ecf316a9547bedf74871f24d1722e3f3cfff" + "sha2": "f439893abc29fa3d1b29d471dd98f96e90ee2697" } ,{ "testCaseDescription": "javascript-subscript-access-variable-replacement-insert-test", @@ -77,9 +77,9 @@ "filePaths": [ "subscript-access-variable.js" ], - "sha1": "a076ecf316a9547bedf74871f24d1722e3f3cfff", + "sha1": "f439893abc29fa3d1b29d471dd98f96e90ee2697", "gitDir": "test/corpus/repos/javascript", - "sha2": "532af784b3b0f34834c09220cae84e8685973ce5" + "sha2": "20336b12a08bcd4c21d5dc3924b33c890e7756f5" } ,{ "testCaseDescription": "javascript-subscript-access-variable-delete-insert-test", @@ -123,9 +123,9 @@ "filePaths": [ "subscript-access-variable.js" ], - "sha1": "532af784b3b0f34834c09220cae84e8685973ce5", + "sha1": "20336b12a08bcd4c21d5dc3924b33c890e7756f5", "gitDir": "test/corpus/repos/javascript", - "sha2": "1d5d4545a5ebd95ec639b5cbd0b8ddf370f6a9bb" + "sha2": "4a075f832e204bbf26ded5314cfb891513b549d6" } ,{ "testCaseDescription": "javascript-subscript-access-variable-replacement-test", @@ -169,9 +169,9 @@ "filePaths": [ "subscript-access-variable.js" ], - "sha1": "1d5d4545a5ebd95ec639b5cbd0b8ddf370f6a9bb", + "sha1": "4a075f832e204bbf26ded5314cfb891513b549d6", "gitDir": "test/corpus/repos/javascript", - "sha2": "f24b4aa4b2d05fa5f999084bc6dc9fb783410c34" + "sha2": "d23a59eb43de72ee6594bb44bc987fc0b650c965" } ,{ "testCaseDescription": "javascript-subscript-access-variable-delete-replacement-test", @@ -236,9 +236,9 @@ "filePaths": [ "subscript-access-variable.js" ], - "sha1": "f24b4aa4b2d05fa5f999084bc6dc9fb783410c34", + "sha1": "d23a59eb43de72ee6594bb44bc987fc0b650c965", "gitDir": "test/corpus/repos/javascript", - "sha2": "4226b1e07671ad870d12e6e5942b38bf608049ab" + "sha2": "255b019fc84f0488a1de3ed0b4f3c3ad28aa365a" } ,{ "testCaseDescription": "javascript-subscript-access-variable-delete-test", @@ -269,9 +269,9 @@ "filePaths": [ "subscript-access-variable.js" ], - "sha1": "4226b1e07671ad870d12e6e5942b38bf608049ab", + "sha1": "255b019fc84f0488a1de3ed0b4f3c3ad28aa365a", "gitDir": "test/corpus/repos/javascript", - "sha2": "e6f147e5c8d95e515d4a599a02e9601d59d95026" + "sha2": "df97f6eeaaa076e805e66e1bcf98403493d92c2f" } ,{ "testCaseDescription": "javascript-subscript-access-variable-delete-rest-test", @@ -302,7 +302,7 @@ "filePaths": [ "subscript-access-variable.js" ], - "sha1": "e6f147e5c8d95e515d4a599a02e9601d59d95026", + "sha1": "df97f6eeaaa076e805e66e1bcf98403493d92c2f", "gitDir": "test/corpus/repos/javascript", - "sha2": "cbebbe0cb3d24a7adb492b88b6b5769c9b895654" + "sha2": "7ae7a3452b9ea0561d469df9ecaf32e6eb2d9474" }] diff --git a/test/corpus/diff-summaries/javascript/switch-statement.json b/test/corpus/diff-summaries/javascript/switch-statement.json index d223a4e32..fc7e5f6d0 100644 --- a/test/corpus/diff-summaries/javascript/switch-statement.json +++ b/test/corpus/diff-summaries/javascript/switch-statement.json @@ -27,9 +27,9 @@ "filePaths": [ "switch-statement.js" ], - "sha1": "9edcc470495aad2ae2b395a18179ec07829ad591", + "sha1": "ebc2ca02f6b0c4744e33e2d191158cc7f2b19a60", "gitDir": "test/corpus/repos/javascript", - "sha2": "1acb22650fd13ec0e21402cea65bcdb4e213de86" + "sha2": "cbc2b0ea47a2cd6fb09368f3c72e101f946c4b26" } ,{ "testCaseDescription": "javascript-switch-statement-replacement-insert-test", @@ -77,9 +77,9 @@ "filePaths": [ "switch-statement.js" ], - "sha1": "1acb22650fd13ec0e21402cea65bcdb4e213de86", + "sha1": "cbc2b0ea47a2cd6fb09368f3c72e101f946c4b26", "gitDir": "test/corpus/repos/javascript", - "sha2": "97c934a7e12be096627bbdd511c6d3ac1b1bfa7e" + "sha2": "e61491adc3ae0a36743a2fb5a3be26e57637593b" } ,{ "testCaseDescription": "javascript-switch-statement-delete-insert-test", @@ -153,9 +153,9 @@ "filePaths": [ "switch-statement.js" ], - "sha1": "97c934a7e12be096627bbdd511c6d3ac1b1bfa7e", + "sha1": "e61491adc3ae0a36743a2fb5a3be26e57637593b", "gitDir": "test/corpus/repos/javascript", - "sha2": "4010f253012dac96ff51ed3ce12d7e4a25962969" + "sha2": "c62f3ccb77ecb50b8f61d3d058f05a27d4187227" } ,{ "testCaseDescription": "javascript-switch-statement-replacement-test", @@ -229,9 +229,9 @@ "filePaths": [ "switch-statement.js" ], - "sha1": "4010f253012dac96ff51ed3ce12d7e4a25962969", + "sha1": "c62f3ccb77ecb50b8f61d3d058f05a27d4187227", "gitDir": "test/corpus/repos/javascript", - "sha2": "c1e7946102306073d5951a4d9636782f92f31e50" + "sha2": "08f399fd747b15cef9703dc4f05efd330258e832" } ,{ "testCaseDescription": "javascript-switch-statement-delete-replacement-test", @@ -296,9 +296,9 @@ "filePaths": [ "switch-statement.js" ], - "sha1": "c1e7946102306073d5951a4d9636782f92f31e50", + "sha1": "08f399fd747b15cef9703dc4f05efd330258e832", "gitDir": "test/corpus/repos/javascript", - "sha2": "23b62bde7c3eca7299b178544ed4684eb2b2c10e" + "sha2": "100b2392d9286d71b1c1910ddacd28ca2a96284b" } ,{ "testCaseDescription": "javascript-switch-statement-delete-test", @@ -329,9 +329,9 @@ "filePaths": [ "switch-statement.js" ], - "sha1": "23b62bde7c3eca7299b178544ed4684eb2b2c10e", + "sha1": "100b2392d9286d71b1c1910ddacd28ca2a96284b", "gitDir": "test/corpus/repos/javascript", - "sha2": "289789d38eff4a6cb05cd1d6f108ce4b891e5cc0" + "sha2": "f033612791a0f3ff8aa0d4313044903cd7eb8b9a" } ,{ "testCaseDescription": "javascript-switch-statement-delete-rest-test", @@ -362,7 +362,7 @@ "filePaths": [ "switch-statement.js" ], - "sha1": "289789d38eff4a6cb05cd1d6f108ce4b891e5cc0", + "sha1": "f033612791a0f3ff8aa0d4313044903cd7eb8b9a", "gitDir": "test/corpus/repos/javascript", - "sha2": "e2ffe71cd07060d1601caa470aa1936a882365aa" + "sha2": "70fe15f33094a3e5dc81081f9bd30e2baa0ff885" }] diff --git a/test/corpus/diff-summaries/javascript/template-string.json b/test/corpus/diff-summaries/javascript/template-string.json index 9282fa911..e73ee73f0 100644 --- a/test/corpus/diff-summaries/javascript/template-string.json +++ b/test/corpus/diff-summaries/javascript/template-string.json @@ -27,9 +27,9 @@ "filePaths": [ "template-string.js" ], - "sha1": "8626ab02829f07b2f15f25da58eb41b69afd53e3", + "sha1": "d3aee735401b2b9c803e3d684ab3c6b96a16898f", "gitDir": "test/corpus/repos/javascript", - "sha2": "d01fd0596a0ab6b147d7424546f7b0996adc1fba" + "sha2": "0bf1b7877627bfb8da6474326584c9caaa1b9bf9" } ,{ "testCaseDescription": "javascript-template-string-replacement-insert-test", @@ -77,9 +77,9 @@ "filePaths": [ "template-string.js" ], - "sha1": "d01fd0596a0ab6b147d7424546f7b0996adc1fba", + "sha1": "0bf1b7877627bfb8da6474326584c9caaa1b9bf9", "gitDir": "test/corpus/repos/javascript", - "sha2": "6e7f81c46d45fea5206a006ceaa2d82ec8f78f61" + "sha2": "36c95439a521f5cb2a91e8139cf324044e753ac9" } ,{ "testCaseDescription": "javascript-template-string-delete-insert-test", @@ -123,9 +123,9 @@ "filePaths": [ "template-string.js" ], - "sha1": "6e7f81c46d45fea5206a006ceaa2d82ec8f78f61", + "sha1": "36c95439a521f5cb2a91e8139cf324044e753ac9", "gitDir": "test/corpus/repos/javascript", - "sha2": "edb72e08b538368a53cf59d2267434e98cc07b0b" + "sha2": "8604dc99b4ccf972649343fdc6a95a17f7823709" } ,{ "testCaseDescription": "javascript-template-string-replacement-test", @@ -169,9 +169,9 @@ "filePaths": [ "template-string.js" ], - "sha1": "edb72e08b538368a53cf59d2267434e98cc07b0b", + "sha1": "8604dc99b4ccf972649343fdc6a95a17f7823709", "gitDir": "test/corpus/repos/javascript", - "sha2": "4d026aa2de0873035dae443cf69517b3e587cb49" + "sha2": "ae3d15a910e3f12cb984f003a26e0f1d480c20c4" } ,{ "testCaseDescription": "javascript-template-string-delete-replacement-test", @@ -236,9 +236,9 @@ "filePaths": [ "template-string.js" ], - "sha1": "4d026aa2de0873035dae443cf69517b3e587cb49", + "sha1": "ae3d15a910e3f12cb984f003a26e0f1d480c20c4", "gitDir": "test/corpus/repos/javascript", - "sha2": "6eeca042e59e8a58d11b6e4829af1da4f297a099" + "sha2": "857c899c43b360b8e15250c028feb13b37472719" } ,{ "testCaseDescription": "javascript-template-string-delete-test", @@ -269,9 +269,9 @@ "filePaths": [ "template-string.js" ], - "sha1": "6eeca042e59e8a58d11b6e4829af1da4f297a099", + "sha1": "857c899c43b360b8e15250c028feb13b37472719", "gitDir": "test/corpus/repos/javascript", - "sha2": "c37aba59f9d510463c64e52a14eb1da928d668ee" + "sha2": "32363666c860768e31d1c805ddee49c819f887a6" } ,{ "testCaseDescription": "javascript-template-string-delete-rest-test", @@ -302,7 +302,7 @@ "filePaths": [ "template-string.js" ], - "sha1": "c37aba59f9d510463c64e52a14eb1da928d668ee", + "sha1": "32363666c860768e31d1c805ddee49c819f887a6", "gitDir": "test/corpus/repos/javascript", - "sha2": "215eb7570ac9ccb686598ee7a6c1ddc9c0562224" + "sha2": "67dfbd7b45236e87dcd260ea7ac3c14b307c474f" }] diff --git a/test/corpus/diff-summaries/javascript/ternary.json b/test/corpus/diff-summaries/javascript/ternary.json index f26c4d027..100ea210d 100644 --- a/test/corpus/diff-summaries/javascript/ternary.json +++ b/test/corpus/diff-summaries/javascript/ternary.json @@ -27,9 +27,9 @@ "filePaths": [ "ternary.js" ], - "sha1": "7086396295d14f41207e8fbae4d350f2672a77dd", + "sha1": "216c9ba07743064780c37d5f07af95a9dee2bf96", "gitDir": "test/corpus/repos/javascript", - "sha2": "8a1fe236a211694d9fb84e254d894597ddaa0cd6" + "sha2": "5a6f3092f70f211e165506d1c3196f24b065f67a" } ,{ "testCaseDescription": "javascript-ternary-replacement-insert-test", @@ -77,9 +77,9 @@ "filePaths": [ "ternary.js" ], - "sha1": "8a1fe236a211694d9fb84e254d894597ddaa0cd6", + "sha1": "5a6f3092f70f211e165506d1c3196f24b065f67a", "gitDir": "test/corpus/repos/javascript", - "sha2": "6ac46b3a4b87fb3a90150d336ad4a8ae1f1b63f7" + "sha2": "b0b8e37ca235cac0f4994d17eb1527cd14e4832b" } ,{ "testCaseDescription": "javascript-ternary-delete-insert-test", @@ -127,9 +127,9 @@ "filePaths": [ "ternary.js" ], - "sha1": "6ac46b3a4b87fb3a90150d336ad4a8ae1f1b63f7", + "sha1": "b0b8e37ca235cac0f4994d17eb1527cd14e4832b", "gitDir": "test/corpus/repos/javascript", - "sha2": "f3c918ef30afcdad6de0e05fa3886964a72b0029" + "sha2": "f7d548f311ce81e47facc215fefc7c734b32f131" } ,{ "testCaseDescription": "javascript-ternary-replacement-test", @@ -177,9 +177,9 @@ "filePaths": [ "ternary.js" ], - "sha1": "f3c918ef30afcdad6de0e05fa3886964a72b0029", + "sha1": "f7d548f311ce81e47facc215fefc7c734b32f131", "gitDir": "test/corpus/repos/javascript", - "sha2": "eda16e19b40607bb335535a7c03378dfb511c030" + "sha2": "30da4a7ee5e6eba51591601b2b9ca9cc24d30494" } ,{ "testCaseDescription": "javascript-ternary-delete-replacement-test", @@ -244,9 +244,9 @@ "filePaths": [ "ternary.js" ], - "sha1": "eda16e19b40607bb335535a7c03378dfb511c030", + "sha1": "30da4a7ee5e6eba51591601b2b9ca9cc24d30494", "gitDir": "test/corpus/repos/javascript", - "sha2": "63a42f2ef52ae2fdb8545cc7153c9b833cee6860" + "sha2": "9fa12d415964908e661b33756b867eb7616e3d94" } ,{ "testCaseDescription": "javascript-ternary-delete-test", @@ -277,9 +277,9 @@ "filePaths": [ "ternary.js" ], - "sha1": "63a42f2ef52ae2fdb8545cc7153c9b833cee6860", + "sha1": "9fa12d415964908e661b33756b867eb7616e3d94", "gitDir": "test/corpus/repos/javascript", - "sha2": "4490621208793b8eefec135b9971666038456188" + "sha2": "8e6ed77f360e132885b2b329a4d26492a32e0f94" } ,{ "testCaseDescription": "javascript-ternary-delete-rest-test", @@ -310,7 +310,7 @@ "filePaths": [ "ternary.js" ], - "sha1": "4490621208793b8eefec135b9971666038456188", + "sha1": "8e6ed77f360e132885b2b329a4d26492a32e0f94", "gitDir": "test/corpus/repos/javascript", - "sha2": "f01711cd334d609eaf2763a3694e94c771e37f3e" + "sha2": "3a53bc319251c49799f5e1229514b74297ef88e4" }] diff --git a/test/corpus/diff-summaries/javascript/this-expression.json b/test/corpus/diff-summaries/javascript/this-expression.json index 9af9977ef..af0a0a6ba 100644 --- a/test/corpus/diff-summaries/javascript/this-expression.json +++ b/test/corpus/diff-summaries/javascript/this-expression.json @@ -27,9 +27,9 @@ "filePaths": [ "this-expression.js" ], - "sha1": "7a8a0da7d72fa0fc4f17e0877fbf7991771801e4", + "sha1": "324ef3f6d6409ee7a42609453d3259490538a470", "gitDir": "test/corpus/repos/javascript", - "sha2": "4e68235a410989b6668d753c43e95d7ea82a20ab" + "sha2": "2823bdb25666f088a22983110b9c71865cd1db71" } ,{ "testCaseDescription": "javascript-this-expression-replacement-insert-test", @@ -77,9 +77,9 @@ "filePaths": [ "this-expression.js" ], - "sha1": "4e68235a410989b6668d753c43e95d7ea82a20ab", + "sha1": "2823bdb25666f088a22983110b9c71865cd1db71", "gitDir": "test/corpus/repos/javascript", - "sha2": "1eaabc425a7661277a9ac52b3e5189db025ad881" + "sha2": "754c24295e09df0536bb63de88f45bf9c870e1fb" } ,{ "testCaseDescription": "javascript-this-expression-delete-insert-test", @@ -127,9 +127,9 @@ "filePaths": [ "this-expression.js" ], - "sha1": "1eaabc425a7661277a9ac52b3e5189db025ad881", + "sha1": "754c24295e09df0536bb63de88f45bf9c870e1fb", "gitDir": "test/corpus/repos/javascript", - "sha2": "ebdf7cb1b6e208ba778abad19c2cbf3ca29266ed" + "sha2": "ec25a6a159d6bae204a5360b0737325faa2b0f1d" } ,{ "testCaseDescription": "javascript-this-expression-replacement-test", @@ -177,9 +177,9 @@ "filePaths": [ "this-expression.js" ], - "sha1": "ebdf7cb1b6e208ba778abad19c2cbf3ca29266ed", + "sha1": "ec25a6a159d6bae204a5360b0737325faa2b0f1d", "gitDir": "test/corpus/repos/javascript", - "sha2": "f7f8f21aeaebe6a982a1f3a21fcdf54bb9015b88" + "sha2": "35fe3d5b2a6524f9c7bbfaa14d4753bd882737b1" } ,{ "testCaseDescription": "javascript-this-expression-delete-replacement-test", @@ -244,9 +244,9 @@ "filePaths": [ "this-expression.js" ], - "sha1": "f7f8f21aeaebe6a982a1f3a21fcdf54bb9015b88", + "sha1": "35fe3d5b2a6524f9c7bbfaa14d4753bd882737b1", "gitDir": "test/corpus/repos/javascript", - "sha2": "d93d9eecbb0719107fe145d07a5ce4acd1e38e2a" + "sha2": "cbdcedd3245da3c85c3f88aa5b28f6ec2a61359e" } ,{ "testCaseDescription": "javascript-this-expression-delete-test", @@ -277,9 +277,9 @@ "filePaths": [ "this-expression.js" ], - "sha1": "d93d9eecbb0719107fe145d07a5ce4acd1e38e2a", + "sha1": "cbdcedd3245da3c85c3f88aa5b28f6ec2a61359e", "gitDir": "test/corpus/repos/javascript", - "sha2": "2cde04d533ec65accf0c7a86021a2f40b593135c" + "sha2": "03fab7b41a417c4a7ba9d0687d775c6036af9794" } ,{ "testCaseDescription": "javascript-this-expression-delete-rest-test", @@ -310,7 +310,7 @@ "filePaths": [ "this-expression.js" ], - "sha1": "2cde04d533ec65accf0c7a86021a2f40b593135c", + "sha1": "03fab7b41a417c4a7ba9d0687d775c6036af9794", "gitDir": "test/corpus/repos/javascript", - "sha2": "e876cda8f0a6a14bd8518d84e985c6616b2f5548" + "sha2": "5e6fd51739eb15db9fcd9e85e7f5c64da736056e" }] diff --git a/test/corpus/diff-summaries/javascript/throw-statement.json b/test/corpus/diff-summaries/javascript/throw-statement.json index 0c071fdd0..ed91508cc 100644 --- a/test/corpus/diff-summaries/javascript/throw-statement.json +++ b/test/corpus/diff-summaries/javascript/throw-statement.json @@ -27,9 +27,9 @@ "filePaths": [ "throw-statement.js" ], - "sha1": "e2ffe71cd07060d1601caa470aa1936a882365aa", + "sha1": "70fe15f33094a3e5dc81081f9bd30e2baa0ff885", "gitDir": "test/corpus/repos/javascript", - "sha2": "363abd980205793325903f7663a8aba813853c60" + "sha2": "16ded5326b4884e9de5e7224f4469f9aae7ecbc8" } ,{ "testCaseDescription": "javascript-throw-statement-replacement-insert-test", @@ -77,9 +77,9 @@ "filePaths": [ "throw-statement.js" ], - "sha1": "363abd980205793325903f7663a8aba813853c60", + "sha1": "16ded5326b4884e9de5e7224f4469f9aae7ecbc8", "gitDir": "test/corpus/repos/javascript", - "sha2": "82955fc3b94492fd9bc3781b544bffd24218c946" + "sha2": "d848598691d350174c103d649fa429508e293ea9" } ,{ "testCaseDescription": "javascript-throw-statement-delete-insert-test", @@ -123,9 +123,9 @@ "filePaths": [ "throw-statement.js" ], - "sha1": "82955fc3b94492fd9bc3781b544bffd24218c946", + "sha1": "d848598691d350174c103d649fa429508e293ea9", "gitDir": "test/corpus/repos/javascript", - "sha2": "f02d91e624715dab97abdc40d8f85c41b03059d3" + "sha2": "2501b7502e6a944405259269fec5f99b807856c8" } ,{ "testCaseDescription": "javascript-throw-statement-replacement-test", @@ -169,9 +169,9 @@ "filePaths": [ "throw-statement.js" ], - "sha1": "f02d91e624715dab97abdc40d8f85c41b03059d3", + "sha1": "2501b7502e6a944405259269fec5f99b807856c8", "gitDir": "test/corpus/repos/javascript", - "sha2": "999ce8327ac58820d2d5bbac312c0848974b628b" + "sha2": "6172a941a9627baa0c7ece469436e3d7eb5e41de" } ,{ "testCaseDescription": "javascript-throw-statement-delete-replacement-test", @@ -236,9 +236,9 @@ "filePaths": [ "throw-statement.js" ], - "sha1": "999ce8327ac58820d2d5bbac312c0848974b628b", + "sha1": "6172a941a9627baa0c7ece469436e3d7eb5e41de", "gitDir": "test/corpus/repos/javascript", - "sha2": "bcb93927bbea7b965623d9fb3be8394b1b4ab89f" + "sha2": "9d70a68cc287b4ad90075701308eca5c1cd843f1" } ,{ "testCaseDescription": "javascript-throw-statement-delete-test", @@ -269,9 +269,9 @@ "filePaths": [ "throw-statement.js" ], - "sha1": "bcb93927bbea7b965623d9fb3be8394b1b4ab89f", + "sha1": "9d70a68cc287b4ad90075701308eca5c1cd843f1", "gitDir": "test/corpus/repos/javascript", - "sha2": "71579a278eeefa1b2d0bb5c8468c399a7e195c06" + "sha2": "807015730993ae0d3e28ddd0b06d20b9adf12492" } ,{ "testCaseDescription": "javascript-throw-statement-delete-rest-test", @@ -302,7 +302,7 @@ "filePaths": [ "throw-statement.js" ], - "sha1": "71579a278eeefa1b2d0bb5c8468c399a7e195c06", + "sha1": "807015730993ae0d3e28ddd0b06d20b9adf12492", "gitDir": "test/corpus/repos/javascript", - "sha2": "5044aaf60e72175bafaddfb99e8e548b34647376" + "sha2": "eb8ac03b17e740cb895c1e398a23ece6b7108422" }] diff --git a/test/corpus/diff-summaries/javascript/true.json b/test/corpus/diff-summaries/javascript/true.json index bb0c8d921..626325496 100644 --- a/test/corpus/diff-summaries/javascript/true.json +++ b/test/corpus/diff-summaries/javascript/true.json @@ -27,9 +27,9 @@ "filePaths": [ "true.js" ], - "sha1": "230a472f82fce3b0be97b48298c0b3db54007c5c", + "sha1": "1629fb4f8707806f5be1e2cef413d2b828064f0b", "gitDir": "test/corpus/repos/javascript", - "sha2": "043d01b853e537966ee01a5f9d9c7290b33ce134" + "sha2": "94cc02f4e6099bf670e487a67e0b4d780932f2cf" } ,{ "testCaseDescription": "javascript-true-replacement-insert-test", @@ -77,9 +77,9 @@ "filePaths": [ "true.js" ], - "sha1": "043d01b853e537966ee01a5f9d9c7290b33ce134", + "sha1": "94cc02f4e6099bf670e487a67e0b4d780932f2cf", "gitDir": "test/corpus/repos/javascript", - "sha2": "02cef50d45506ede85c96b11f33bd059c89f5ee7" + "sha2": "356f076ff1abcc3dd92cf1a55175b4fa93736565" } ,{ "testCaseDescription": "javascript-true-delete-insert-test", @@ -127,9 +127,9 @@ "filePaths": [ "true.js" ], - "sha1": "02cef50d45506ede85c96b11f33bd059c89f5ee7", + "sha1": "356f076ff1abcc3dd92cf1a55175b4fa93736565", "gitDir": "test/corpus/repos/javascript", - "sha2": "b170ce196e79b7886a3e2dc39a834228cc8d6374" + "sha2": "9581e3270470aac80cd09c9512dab08e0aebc733" } ,{ "testCaseDescription": "javascript-true-replacement-test", @@ -177,9 +177,9 @@ "filePaths": [ "true.js" ], - "sha1": "b170ce196e79b7886a3e2dc39a834228cc8d6374", + "sha1": "9581e3270470aac80cd09c9512dab08e0aebc733", "gitDir": "test/corpus/repos/javascript", - "sha2": "1630f9afc6e883c6054d6c17d079b5a021d60314" + "sha2": "561495b8d383328d5e897ddda7e1faba194f69ae" } ,{ "testCaseDescription": "javascript-true-delete-replacement-test", @@ -244,9 +244,9 @@ "filePaths": [ "true.js" ], - "sha1": "1630f9afc6e883c6054d6c17d079b5a021d60314", + "sha1": "561495b8d383328d5e897ddda7e1faba194f69ae", "gitDir": "test/corpus/repos/javascript", - "sha2": "53420b8c2df9618edf44659f29dbf259aa768aa4" + "sha2": "471d26ce0f0e66973181d3912a27a619ad3a8795" } ,{ "testCaseDescription": "javascript-true-delete-test", @@ -277,9 +277,9 @@ "filePaths": [ "true.js" ], - "sha1": "53420b8c2df9618edf44659f29dbf259aa768aa4", + "sha1": "471d26ce0f0e66973181d3912a27a619ad3a8795", "gitDir": "test/corpus/repos/javascript", - "sha2": "21ba042d79f5a739f4873d860802f39b15299d6b" + "sha2": "e6498022517e3044ed8c9cd284c82ace50342a7c" } ,{ "testCaseDescription": "javascript-true-delete-rest-test", @@ -310,7 +310,7 @@ "filePaths": [ "true.js" ], - "sha1": "21ba042d79f5a739f4873d860802f39b15299d6b", + "sha1": "e6498022517e3044ed8c9cd284c82ace50342a7c", "gitDir": "test/corpus/repos/javascript", - "sha2": "9c5eadaa5e35756fff0d96ba9830a7e0dbf30fd7" + "sha2": "2729ff0e359b38bda1f650d3283d4116dc2fa3ad" }] diff --git a/test/corpus/diff-summaries/javascript/try-statement.json b/test/corpus/diff-summaries/javascript/try-statement.json index 9640a7d15..a2f9426d7 100644 --- a/test/corpus/diff-summaries/javascript/try-statement.json +++ b/test/corpus/diff-summaries/javascript/try-statement.json @@ -27,9 +27,9 @@ "filePaths": [ "try-statement.js" ], - "sha1": "5044aaf60e72175bafaddfb99e8e548b34647376", + "sha1": "eb8ac03b17e740cb895c1e398a23ece6b7108422", "gitDir": "test/corpus/repos/javascript", - "sha2": "934746aee66c0c2cb37cb4affbb09ff6c9c896e4" + "sha2": "5934d5c231a7d9ae7cbe9b332296d7b6d82b59df" } ,{ "testCaseDescription": "javascript-try-statement-replacement-insert-test", @@ -77,9 +77,9 @@ "filePaths": [ "try-statement.js" ], - "sha1": "934746aee66c0c2cb37cb4affbb09ff6c9c896e4", + "sha1": "5934d5c231a7d9ae7cbe9b332296d7b6d82b59df", "gitDir": "test/corpus/repos/javascript", - "sha2": "3ca670bfa75c6a1708e8cbefcf5709baf85165b9" + "sha2": "f0ea450f12fa45c3ce41f2f8178719797116a3bb" } ,{ "testCaseDescription": "javascript-try-statement-delete-insert-test", @@ -153,9 +153,9 @@ "filePaths": [ "try-statement.js" ], - "sha1": "3ca670bfa75c6a1708e8cbefcf5709baf85165b9", + "sha1": "f0ea450f12fa45c3ce41f2f8178719797116a3bb", "gitDir": "test/corpus/repos/javascript", - "sha2": "e509b6253596a24c3c4d49f53e7354d5415f6406" + "sha2": "1995a3278e3b1009112f4b37f8c0d9215f81468c" } ,{ "testCaseDescription": "javascript-try-statement-replacement-test", @@ -229,9 +229,9 @@ "filePaths": [ "try-statement.js" ], - "sha1": "e509b6253596a24c3c4d49f53e7354d5415f6406", + "sha1": "1995a3278e3b1009112f4b37f8c0d9215f81468c", "gitDir": "test/corpus/repos/javascript", - "sha2": "5539c67fd84c944d395de1bc1d849cdbc54508f4" + "sha2": "031540f54220001ba27ec1c6f7f573d5c360c0a3" } ,{ "testCaseDescription": "javascript-try-statement-delete-replacement-test", @@ -296,9 +296,9 @@ "filePaths": [ "try-statement.js" ], - "sha1": "5539c67fd84c944d395de1bc1d849cdbc54508f4", + "sha1": "031540f54220001ba27ec1c6f7f573d5c360c0a3", "gitDir": "test/corpus/repos/javascript", - "sha2": "159cfefd0e09b1a6cfdce7f7d7707aeff6837fd6" + "sha2": "1f15321135b2625ac1f1ac294f56d03ca22bf3e4" } ,{ "testCaseDescription": "javascript-try-statement-delete-test", @@ -329,9 +329,9 @@ "filePaths": [ "try-statement.js" ], - "sha1": "159cfefd0e09b1a6cfdce7f7d7707aeff6837fd6", + "sha1": "1f15321135b2625ac1f1ac294f56d03ca22bf3e4", "gitDir": "test/corpus/repos/javascript", - "sha2": "5063e245f1b1e2359cd10f7c01c184d103371810" + "sha2": "19bdd1121f08b296b9c29125cc2ce914b97eec82" } ,{ "testCaseDescription": "javascript-try-statement-delete-rest-test", @@ -362,7 +362,7 @@ "filePaths": [ "try-statement.js" ], - "sha1": "5063e245f1b1e2359cd10f7c01c184d103371810", + "sha1": "19bdd1121f08b296b9c29125cc2ce914b97eec82", "gitDir": "test/corpus/repos/javascript", - "sha2": "0578f24cf85fce35bd787e60e1b210b79f462858" + "sha2": "a23b0a588d860380edd5b815810c34e35d5855a8" }] diff --git a/test/corpus/diff-summaries/javascript/type-operator.json b/test/corpus/diff-summaries/javascript/type-operator.json index 4c63329c7..cdef1b2ae 100644 --- a/test/corpus/diff-summaries/javascript/type-operator.json +++ b/test/corpus/diff-summaries/javascript/type-operator.json @@ -27,9 +27,9 @@ "filePaths": [ "type-operator.js" ], - "sha1": "f01711cd334d609eaf2763a3694e94c771e37f3e", + "sha1": "3a53bc319251c49799f5e1229514b74297ef88e4", "gitDir": "test/corpus/repos/javascript", - "sha2": "96aea0eed428b6b20488c222205f76ef2062a771" + "sha2": "88f1751f62f6e08907661f4817436a3686c1db71" } ,{ "testCaseDescription": "javascript-type-operator-replacement-insert-test", @@ -77,9 +77,9 @@ "filePaths": [ "type-operator.js" ], - "sha1": "96aea0eed428b6b20488c222205f76ef2062a771", + "sha1": "88f1751f62f6e08907661f4817436a3686c1db71", "gitDir": "test/corpus/repos/javascript", - "sha2": "fa1b6db09e23a79415409fd5819d7a559b45adbb" + "sha2": "2dbfcfa73dbc738e8b2194799fb7d737f5cbf32c" } ,{ "testCaseDescription": "javascript-type-operator-delete-insert-test", @@ -110,9 +110,9 @@ "filePaths": [ "type-operator.js" ], - "sha1": "fa1b6db09e23a79415409fd5819d7a559b45adbb", + "sha1": "2dbfcfa73dbc738e8b2194799fb7d737f5cbf32c", "gitDir": "test/corpus/repos/javascript", - "sha2": "73adba630bdf30c6bb43d2c586709818346f2ad0" + "sha2": "01a5f643661510a0da476bfa9dcd740b35417497" } ,{ "testCaseDescription": "javascript-type-operator-replacement-test", @@ -143,9 +143,9 @@ "filePaths": [ "type-operator.js" ], - "sha1": "73adba630bdf30c6bb43d2c586709818346f2ad0", + "sha1": "01a5f643661510a0da476bfa9dcd740b35417497", "gitDir": "test/corpus/repos/javascript", - "sha2": "237bcf10f4bcbef5839bbb29d3a4985521581f5a" + "sha2": "d1c04495339ea50e222bf286dcba37f841623773" } ,{ "testCaseDescription": "javascript-type-operator-delete-replacement-test", @@ -210,9 +210,9 @@ "filePaths": [ "type-operator.js" ], - "sha1": "237bcf10f4bcbef5839bbb29d3a4985521581f5a", + "sha1": "d1c04495339ea50e222bf286dcba37f841623773", "gitDir": "test/corpus/repos/javascript", - "sha2": "6b290f9e3aba6406475e0ffb0012267e34bb829d" + "sha2": "df838082db78f590e0fe548d501573688c41e6e6" } ,{ "testCaseDescription": "javascript-type-operator-delete-test", @@ -243,9 +243,9 @@ "filePaths": [ "type-operator.js" ], - "sha1": "6b290f9e3aba6406475e0ffb0012267e34bb829d", + "sha1": "df838082db78f590e0fe548d501573688c41e6e6", "gitDir": "test/corpus/repos/javascript", - "sha2": "55f9cf52fbcb6cfdfc385b794e42e97d713a3ab2" + "sha2": "a4c2f82fa95065ae07a082ab5cac594e41e552db" } ,{ "testCaseDescription": "javascript-type-operator-delete-rest-test", @@ -276,7 +276,7 @@ "filePaths": [ "type-operator.js" ], - "sha1": "55f9cf52fbcb6cfdfc385b794e42e97d713a3ab2", + "sha1": "a4c2f82fa95065ae07a082ab5cac594e41e552db", "gitDir": "test/corpus/repos/javascript", - "sha2": "c012557afb55395556a9209537f977c480c9cfa2" + "sha2": "215414e0397973e2f7d49a8edff9cf1d84fad02a" }] diff --git a/test/corpus/diff-summaries/javascript/undefined.json b/test/corpus/diff-summaries/javascript/undefined.json index 5079ef9a4..ea0245846 100644 --- a/test/corpus/diff-summaries/javascript/undefined.json +++ b/test/corpus/diff-summaries/javascript/undefined.json @@ -27,9 +27,9 @@ "filePaths": [ "undefined.js" ], - "sha1": "c4cbb6a4ff71852691d643f686d8231c9a3989a4", + "sha1": "0cf324666c04ffe5413f3e03ff09dc4a3883ab7c", "gitDir": "test/corpus/repos/javascript", - "sha2": "fcd961d200815be0e5df9acbd6d7948232c2cff8" + "sha2": "903a9a541686eb72e2368433c52c1629471946bb" } ,{ "testCaseDescription": "javascript-undefined-replacement-insert-test", @@ -77,9 +77,9 @@ "filePaths": [ "undefined.js" ], - "sha1": "fcd961d200815be0e5df9acbd6d7948232c2cff8", + "sha1": "903a9a541686eb72e2368433c52c1629471946bb", "gitDir": "test/corpus/repos/javascript", - "sha2": "80316664f17060feb76cb3394afce3e4bb645e32" + "sha2": "ad1a018329b77e1b61390ecf5e41ac819621092f" } ,{ "testCaseDescription": "javascript-undefined-delete-insert-test", @@ -127,9 +127,9 @@ "filePaths": [ "undefined.js" ], - "sha1": "80316664f17060feb76cb3394afce3e4bb645e32", + "sha1": "ad1a018329b77e1b61390ecf5e41ac819621092f", "gitDir": "test/corpus/repos/javascript", - "sha2": "4f95a9bf9510322e9a6bf79636e45b35a0480a7c" + "sha2": "b7e10abedf4f7deda145e91e0462dbe4c1a9956c" } ,{ "testCaseDescription": "javascript-undefined-replacement-test", @@ -177,9 +177,9 @@ "filePaths": [ "undefined.js" ], - "sha1": "4f95a9bf9510322e9a6bf79636e45b35a0480a7c", + "sha1": "b7e10abedf4f7deda145e91e0462dbe4c1a9956c", "gitDir": "test/corpus/repos/javascript", - "sha2": "994be2b836b9ef3f76478f77e08fbcae2db003c2" + "sha2": "bd83760f930bd0e4710cb3a9f66c682417a36ed8" } ,{ "testCaseDescription": "javascript-undefined-delete-replacement-test", @@ -244,9 +244,9 @@ "filePaths": [ "undefined.js" ], - "sha1": "994be2b836b9ef3f76478f77e08fbcae2db003c2", + "sha1": "bd83760f930bd0e4710cb3a9f66c682417a36ed8", "gitDir": "test/corpus/repos/javascript", - "sha2": "cd8d3a76c8a21b9cd938996afa84066513b5292c" + "sha2": "5ad97c97a2128df95602077d624479ec65a04124" } ,{ "testCaseDescription": "javascript-undefined-delete-test", @@ -277,9 +277,9 @@ "filePaths": [ "undefined.js" ], - "sha1": "cd8d3a76c8a21b9cd938996afa84066513b5292c", + "sha1": "5ad97c97a2128df95602077d624479ec65a04124", "gitDir": "test/corpus/repos/javascript", - "sha2": "e202ac5fe4d20d33ab4e89cc92d6e0a70f685811" + "sha2": "1ba67fdc33e9717a6b1aa69e380897fed2a034e7" } ,{ "testCaseDescription": "javascript-undefined-delete-rest-test", @@ -310,7 +310,7 @@ "filePaths": [ "undefined.js" ], - "sha1": "e202ac5fe4d20d33ab4e89cc92d6e0a70f685811", + "sha1": "1ba67fdc33e9717a6b1aa69e380897fed2a034e7", "gitDir": "test/corpus/repos/javascript", - "sha2": "230a472f82fce3b0be97b48298c0b3db54007c5c" + "sha2": "1629fb4f8707806f5be1e2cef413d2b828064f0b" }] diff --git a/test/corpus/diff-summaries/javascript/var-declaration.json b/test/corpus/diff-summaries/javascript/var-declaration.json index 1d16fc958..be928d8ac 100644 --- a/test/corpus/diff-summaries/javascript/var-declaration.json +++ b/test/corpus/diff-summaries/javascript/var-declaration.json @@ -27,9 +27,9 @@ "filePaths": [ "var-declaration.js" ], - "sha1": "9f1361ad761d81ff9d3b968ebeefa0f9640ae0ca", + "sha1": "b9adfaa1ed76ab8073a888953b9f52ed07ae901d", "gitDir": "test/corpus/repos/javascript", - "sha2": "a8c2f82710f1241c44e40cee6ca80a095ea851e3" + "sha2": "e7fb4ec50d4b102631cb919440f306001a37e6dc" } ,{ "testCaseDescription": "javascript-var-declaration-replacement-insert-test", @@ -111,9 +111,9 @@ "filePaths": [ "var-declaration.js" ], - "sha1": "a8c2f82710f1241c44e40cee6ca80a095ea851e3", + "sha1": "e7fb4ec50d4b102631cb919440f306001a37e6dc", "gitDir": "test/corpus/repos/javascript", - "sha2": "43e3fc6013d5fc2f1db341fde7f4fe9ea060e7e1" + "sha2": "64e82b7c2ba46e720224dd265772025e78cb70b7" } ,{ "testCaseDescription": "javascript-var-declaration-delete-insert-test", @@ -191,9 +191,9 @@ "filePaths": [ "var-declaration.js" ], - "sha1": "43e3fc6013d5fc2f1db341fde7f4fe9ea060e7e1", + "sha1": "64e82b7c2ba46e720224dd265772025e78cb70b7", "gitDir": "test/corpus/repos/javascript", - "sha2": "c3ea199c46ebfe632dad05ad20bdfb776835a9d5" + "sha2": "483b3edb575f17ee20c8211977b74f5cb16d0be0" } ,{ "testCaseDescription": "javascript-var-declaration-replacement-test", @@ -271,9 +271,9 @@ "filePaths": [ "var-declaration.js" ], - "sha1": "c3ea199c46ebfe632dad05ad20bdfb776835a9d5", + "sha1": "483b3edb575f17ee20c8211977b74f5cb16d0be0", "gitDir": "test/corpus/repos/javascript", - "sha2": "70e0141884fe614c029ceab9cabb24ac689f8c50" + "sha2": "205c09348c66d5fece285d675cf454357adb5493" } ,{ "testCaseDescription": "javascript-var-declaration-delete-replacement-test", @@ -406,9 +406,9 @@ "filePaths": [ "var-declaration.js" ], - "sha1": "70e0141884fe614c029ceab9cabb24ac689f8c50", + "sha1": "205c09348c66d5fece285d675cf454357adb5493", "gitDir": "test/corpus/repos/javascript", - "sha2": "f4ebb1027bebfbeacd6fbb4a6e1f16e2423ee62e" + "sha2": "d7d8aa3680790caf2b3c5140a3bf7dac3db9d341" } ,{ "testCaseDescription": "javascript-var-declaration-delete-test", @@ -439,9 +439,9 @@ "filePaths": [ "var-declaration.js" ], - "sha1": "f4ebb1027bebfbeacd6fbb4a6e1f16e2423ee62e", + "sha1": "d7d8aa3680790caf2b3c5140a3bf7dac3db9d341", "gitDir": "test/corpus/repos/javascript", - "sha2": "e18b5c0b82a5bdf95e7977d7947e44d872d5abfc" + "sha2": "71422bb2b7a22e8005be0975966a8b8aecab9acb" } ,{ "testCaseDescription": "javascript-var-declaration-delete-rest-test", @@ -506,7 +506,7 @@ "filePaths": [ "var-declaration.js" ], - "sha1": "e18b5c0b82a5bdf95e7977d7947e44d872d5abfc", + "sha1": "71422bb2b7a22e8005be0975966a8b8aecab9acb", "gitDir": "test/corpus/repos/javascript", - "sha2": "a67c36dee6afa77efd8005ab23227f683239d35e" + "sha2": "72fe137f23a68d773c76719f790807ead00ef84a" }] diff --git a/test/corpus/diff-summaries/javascript/variable.json b/test/corpus/diff-summaries/javascript/variable.json index e609d95e0..81087dddf 100644 --- a/test/corpus/diff-summaries/javascript/variable.json +++ b/test/corpus/diff-summaries/javascript/variable.json @@ -27,9 +27,9 @@ "filePaths": [ "variable.js" ], - "sha1": "4df21e328803748f18b7cd64862f776a275b1448", + "sha1": "45a6d97047c9425f56128ec4e4400027be11cad7", "gitDir": "test/corpus/repos/javascript", - "sha2": "a3840d75920054be5279d78807096889c4c989c9" + "sha2": "9dad141263720dcf07ceb13d01029c69bcef38ea" } ,{ "testCaseDescription": "javascript-variable-replacement-insert-test", @@ -77,9 +77,9 @@ "filePaths": [ "variable.js" ], - "sha1": "a3840d75920054be5279d78807096889c4c989c9", + "sha1": "9dad141263720dcf07ceb13d01029c69bcef38ea", "gitDir": "test/corpus/repos/javascript", - "sha2": "a42caa0fda1bdb5b316d718758cbf4a51861c2b2" + "sha2": "4f6333428bf9465cdab6df21470f1787d3bff8d7" } ,{ "testCaseDescription": "javascript-variable-delete-insert-test", @@ -123,9 +123,9 @@ "filePaths": [ "variable.js" ], - "sha1": "a42caa0fda1bdb5b316d718758cbf4a51861c2b2", + "sha1": "4f6333428bf9465cdab6df21470f1787d3bff8d7", "gitDir": "test/corpus/repos/javascript", - "sha2": "16873fbd755c8e72f25d8aa042c4d2f837cfd23f" + "sha2": "f5e4df4fc4b3baf6dabfad4aee94248f5ba36189" } ,{ "testCaseDescription": "javascript-variable-replacement-test", @@ -169,9 +169,9 @@ "filePaths": [ "variable.js" ], - "sha1": "16873fbd755c8e72f25d8aa042c4d2f837cfd23f", + "sha1": "f5e4df4fc4b3baf6dabfad4aee94248f5ba36189", "gitDir": "test/corpus/repos/javascript", - "sha2": "0d06b024a50e68aa79d056bc76fdec5e6e640ef3" + "sha2": "6c86ef3484ecc568dfff6dc7d6bf603ac8dc8fcd" } ,{ "testCaseDescription": "javascript-variable-delete-replacement-test", @@ -236,9 +236,9 @@ "filePaths": [ "variable.js" ], - "sha1": "0d06b024a50e68aa79d056bc76fdec5e6e640ef3", + "sha1": "6c86ef3484ecc568dfff6dc7d6bf603ac8dc8fcd", "gitDir": "test/corpus/repos/javascript", - "sha2": "191cfbfac32bb38d5d4b5bf0c008c473e8302fd4" + "sha2": "a41e6666d1ea0ed4c08217d4aa16d53fcde04f5e" } ,{ "testCaseDescription": "javascript-variable-delete-test", @@ -269,9 +269,9 @@ "filePaths": [ "variable.js" ], - "sha1": "191cfbfac32bb38d5d4b5bf0c008c473e8302fd4", + "sha1": "a41e6666d1ea0ed4c08217d4aa16d53fcde04f5e", "gitDir": "test/corpus/repos/javascript", - "sha2": "690d29ead8ccc9c917669062891777ba61074c53" + "sha2": "dbf27da132fca11e0fd7163c0bc5583fdd85f37c" } ,{ "testCaseDescription": "javascript-variable-delete-rest-test", @@ -302,7 +302,7 @@ "filePaths": [ "variable.js" ], - "sha1": "690d29ead8ccc9c917669062891777ba61074c53", + "sha1": "dbf27da132fca11e0fd7163c0bc5583fdd85f37c", "gitDir": "test/corpus/repos/javascript", - "sha2": "8bed39ae9a7d7acce7400df7173470825fa46cb0" + "sha2": "1917c441d2b5dc77f63539a5df1e3cd7f0df97f3" }] diff --git a/test/corpus/diff-summaries/javascript/void-operator.json b/test/corpus/diff-summaries/javascript/void-operator.json index af2b96df7..49339ba0b 100644 --- a/test/corpus/diff-summaries/javascript/void-operator.json +++ b/test/corpus/diff-summaries/javascript/void-operator.json @@ -27,9 +27,9 @@ "filePaths": [ "void-operator.js" ], - "sha1": "4c9359461db3f23921b2af834190b8c9966fa455", + "sha1": "9dd33ff948d47044417ab8a6cb2dd82903a8a1b4", "gitDir": "test/corpus/repos/javascript", - "sha2": "0d445752b33202f03c21c0f575075b54b75d594f" + "sha2": "b0f3ec4fd9d9fd71059a3ae6e64697c1f9fb7d15" } ,{ "testCaseDescription": "javascript-void-operator-replacement-insert-test", @@ -77,9 +77,9 @@ "filePaths": [ "void-operator.js" ], - "sha1": "0d445752b33202f03c21c0f575075b54b75d594f", + "sha1": "b0f3ec4fd9d9fd71059a3ae6e64697c1f9fb7d15", "gitDir": "test/corpus/repos/javascript", - "sha2": "6084c7a622486376a750e062b57485ba15ce33d7" + "sha2": "90c01b59c54d23c04146dda988090b77a29ed5bb" } ,{ "testCaseDescription": "javascript-void-operator-delete-insert-test", @@ -123,9 +123,9 @@ "filePaths": [ "void-operator.js" ], - "sha1": "6084c7a622486376a750e062b57485ba15ce33d7", + "sha1": "90c01b59c54d23c04146dda988090b77a29ed5bb", "gitDir": "test/corpus/repos/javascript", - "sha2": "bd8157de0083725f324c0b07300ab40b761faf9a" + "sha2": "7a4959d77283a38b9e8b8c12dba589465b0fb8f2" } ,{ "testCaseDescription": "javascript-void-operator-replacement-test", @@ -169,9 +169,9 @@ "filePaths": [ "void-operator.js" ], - "sha1": "bd8157de0083725f324c0b07300ab40b761faf9a", + "sha1": "7a4959d77283a38b9e8b8c12dba589465b0fb8f2", "gitDir": "test/corpus/repos/javascript", - "sha2": "822356e36fe70b7e90fde40d96cf3ea636f80238" + "sha2": "8354c0746eacdabc13749e42dc63fad7bfb50a93" } ,{ "testCaseDescription": "javascript-void-operator-delete-replacement-test", @@ -236,9 +236,9 @@ "filePaths": [ "void-operator.js" ], - "sha1": "822356e36fe70b7e90fde40d96cf3ea636f80238", + "sha1": "8354c0746eacdabc13749e42dc63fad7bfb50a93", "gitDir": "test/corpus/repos/javascript", - "sha2": "d7082a08524da8cf4d379c767819b756b9970d34" + "sha2": "0b94a16d84a2dad46c1e6dc0a865da9b5c88c70f" } ,{ "testCaseDescription": "javascript-void-operator-delete-test", @@ -269,9 +269,9 @@ "filePaths": [ "void-operator.js" ], - "sha1": "d7082a08524da8cf4d379c767819b756b9970d34", + "sha1": "0b94a16d84a2dad46c1e6dc0a865da9b5c88c70f", "gitDir": "test/corpus/repos/javascript", - "sha2": "19112b8b21566d018b1fbb073d3e3211067d653c" + "sha2": "27c04d4aef34178ffa822edd57c607fa3ff5ce03" } ,{ "testCaseDescription": "javascript-void-operator-delete-rest-test", @@ -302,7 +302,7 @@ "filePaths": [ "void-operator.js" ], - "sha1": "19112b8b21566d018b1fbb073d3e3211067d653c", + "sha1": "27c04d4aef34178ffa822edd57c607fa3ff5ce03", "gitDir": "test/corpus/repos/javascript", - "sha2": "de1bc70d66645688aab217b87e9d472a34e42bd1" + "sha2": "d1711a33e14ac0a6c516afdd4885511a60f6a194" }] diff --git a/test/corpus/diff-summaries/javascript/while-statement.json b/test/corpus/diff-summaries/javascript/while-statement.json index e6c45c7b6..fa3201697 100644 --- a/test/corpus/diff-summaries/javascript/while-statement.json +++ b/test/corpus/diff-summaries/javascript/while-statement.json @@ -27,9 +27,9 @@ "filePaths": [ "while-statement.js" ], - "sha1": "4baec39517b6fe2e913b63502b66c0f5bb4ad2cc", + "sha1": "7f97f2e3a13baab2548b10a72e291b71ca0b9fa4", "gitDir": "test/corpus/repos/javascript", - "sha2": "9e37955434527f912890ae216acc3ae299622141" + "sha2": "9704581566ea216ec6f378e5f76e8943a79865f5" } ,{ "testCaseDescription": "javascript-while-statement-replacement-insert-test", @@ -77,9 +77,9 @@ "filePaths": [ "while-statement.js" ], - "sha1": "9e37955434527f912890ae216acc3ae299622141", + "sha1": "9704581566ea216ec6f378e5f76e8943a79865f5", "gitDir": "test/corpus/repos/javascript", - "sha2": "f7b70918071a6521eaef2c5be1b3ac9720841446" + "sha2": "fd7989e23defab92f730cb28cfdd04b4c9e2d31b" } ,{ "testCaseDescription": "javascript-while-statement-delete-insert-test", @@ -153,9 +153,9 @@ "filePaths": [ "while-statement.js" ], - "sha1": "f7b70918071a6521eaef2c5be1b3ac9720841446", + "sha1": "fd7989e23defab92f730cb28cfdd04b4c9e2d31b", "gitDir": "test/corpus/repos/javascript", - "sha2": "29c8ebffa11db7289ab51f57efd175f77bd733bd" + "sha2": "9200999bd304f0dd206ad4fa0f6b52807b27b2b4" } ,{ "testCaseDescription": "javascript-while-statement-replacement-test", @@ -229,9 +229,9 @@ "filePaths": [ "while-statement.js" ], - "sha1": "29c8ebffa11db7289ab51f57efd175f77bd733bd", + "sha1": "9200999bd304f0dd206ad4fa0f6b52807b27b2b4", "gitDir": "test/corpus/repos/javascript", - "sha2": "f4d194f2e3d461c76413a90b0d2313ca005b9dfc" + "sha2": "2f2ca40848a11ece5334c303c012b3e46020fb7a" } ,{ "testCaseDescription": "javascript-while-statement-delete-replacement-test", @@ -296,9 +296,9 @@ "filePaths": [ "while-statement.js" ], - "sha1": "f4d194f2e3d461c76413a90b0d2313ca005b9dfc", + "sha1": "2f2ca40848a11ece5334c303c012b3e46020fb7a", "gitDir": "test/corpus/repos/javascript", - "sha2": "a04a222d36c3f3af7c33b093cc2478968ae3651e" + "sha2": "e048bb9d6a69bfd30b01c3ee83d5d28803dcfb57" } ,{ "testCaseDescription": "javascript-while-statement-delete-test", @@ -329,9 +329,9 @@ "filePaths": [ "while-statement.js" ], - "sha1": "a04a222d36c3f3af7c33b093cc2478968ae3651e", + "sha1": "e048bb9d6a69bfd30b01c3ee83d5d28803dcfb57", "gitDir": "test/corpus/repos/javascript", - "sha2": "72f779a1fb746477acef381391603e40efb5ff43" + "sha2": "1628b7a59734cf69c9965cadbe93776d2923085a" } ,{ "testCaseDescription": "javascript-while-statement-delete-rest-test", @@ -362,7 +362,7 @@ "filePaths": [ "while-statement.js" ], - "sha1": "72f779a1fb746477acef381391603e40efb5ff43", + "sha1": "1628b7a59734cf69c9965cadbe93776d2923085a", "gitDir": "test/corpus/repos/javascript", - "sha2": "2991c8cdbe1144d3164c0fc0075cb5388e06583b" + "sha2": "b9bce32850180705594c7350911bd0714243f188" }] diff --git a/test/corpus/repos/javascript b/test/corpus/repos/javascript index 25d0dca67..f8683054b 160000 --- a/test/corpus/repos/javascript +++ b/test/corpus/repos/javascript @@ -1 +1 @@ -Subproject commit 25d0dca67cfd26a4d408ec7cc751b428dd7d0451 +Subproject commit f8683054b3df6a44185993d0c11c1edcf4477b16 From a9d216608fc9daef9e2e5144433763fd14fdf045 Mon Sep 17 00:00:00 2001 From: joshvera Date: Tue, 11 Oct 2016 11:52:49 -0400 Subject: [PATCH 18/27] Rename this/that/these to delete/insert/replace for consistency with Patch --- src/SourceSpan.hs | 12 ++++++------ 1 file changed, 6 insertions(+), 6 deletions(-) diff --git a/src/SourceSpan.hs b/src/SourceSpan.hs index 112191eba..0c6625a94 100644 --- a/src/SourceSpan.hs +++ b/src/SourceSpan.hs @@ -81,13 +81,13 @@ newtype SourceSpans = SourceSpans { unSourceSpans :: These SourceSpan SourceSpan instance A.ToJSON SourceSpans where toJSON (SourceSpans spans) = case spans of - (This span) -> A.object ["this" .= span] - (That span) -> A.object ["that" .= span] - (These span1 span2) -> A.object ["these" .= (span1, span2)] + (This span) -> A.object ["delete" .= span] + (That span) -> A.object ["insert" .= span] + (These span1 span2) -> A.object ["replace" .= (span1, span2)] toEncoding (SourceSpans spans) = case spans of - (This span) -> A.pairs $ "this" .= span - (That span) -> A.pairs $ "that" .= span - (These span1 span2) -> A.pairs $ "these" .= (span1, span2) + (This span) -> A.pairs $ "delete" .= span + (That span) -> A.pairs $ "insert" .= span + (These span1 span2) -> A.pairs $ "replace" .= (span1, span2) instance Arbitrary SourcePos where arbitrary = SourcePos <$> arbitrary <*> arbitrary From 4fb07c28b62983602ad80187fcbccd2d594d2405 Mon Sep 17 00:00:00 2001 From: joshvera Date: Tue, 11 Oct 2016 11:54:47 -0400 Subject: [PATCH 19/27] Bump tests --- .../javascript/anonymous-function.json | 60 ++++++++-------- .../anonymous-parameterless-function.json | 48 ++++++------- .../diff-summaries/javascript/array.json | 48 ++++++------- .../javascript/arrow-function.json | 48 ++++++------- .../diff-summaries/javascript/assignment.json | 48 ++++++------- .../javascript/bitwise-operator.json | 48 ++++++------- .../javascript/boolean-operator.json | 40 +++++------ .../javascript/chained-callbacks.json | 56 +++++++-------- .../javascript/chained-property-access.json | 52 +++++++------- .../diff-summaries/javascript/class.json | 56 +++++++-------- .../javascript/comma-operator.json | 64 ++++++++--------- .../diff-summaries/javascript/comment.json | 48 ++++++------- .../javascript/constructor-call.json | 48 ++++++------- .../javascript/delete-operator.json | 48 ++++++------- .../javascript/do-while-statement.json | 52 +++++++------- .../diff-summaries/javascript/false.json | 52 +++++++------- .../javascript/for-in-statement.json | 56 +++++++-------- .../for-loop-with-in-statement.json | 52 +++++++------- .../javascript/for-of-statement.json | 56 +++++++-------- .../javascript/for-statement.json | 48 ++++++------- .../javascript/function-call-args.json | 68 +++++++++--------- .../javascript/function-call.json | 48 ++++++------- .../diff-summaries/javascript/function.json | 48 ++++++------- .../javascript/generator-function.json | 48 ++++++------- .../diff-summaries/javascript/identifier.json | 48 ++++++------- .../diff-summaries/javascript/if-else.json | 48 ++++++------- test/corpus/diff-summaries/javascript/if.json | 48 ++++++------- .../javascript/math-assignment-operator.json | 48 ++++++------- .../javascript/math-operator.json | 52 +++++++------- .../javascript/member-access-assignment.json | 48 ++++++------- .../javascript/member-access.json | 48 ++++++------- .../javascript/method-call.json | 48 ++++++------- .../javascript/named-function.json | 64 ++++++++--------- .../javascript/nested-functions.json | 52 +++++++------- .../diff-summaries/javascript/null.json | 52 +++++++------- .../diff-summaries/javascript/number.json | 48 ++++++------- .../javascript/object-with-methods.json | 48 ++++++------- .../diff-summaries/javascript/object.json | 52 +++++++------- .../diff-summaries/javascript/regex.json | 48 ++++++------- .../javascript/relational-operator.json | 40 +++++------ .../javascript/return-statement.json | 48 ++++++------- .../diff-summaries/javascript/string.json | 48 ++++++------- .../subscript-access-assignment.json | 48 ++++++------- .../javascript/subscript-access-string.json | 48 ++++++------- .../javascript/subscript-access-variable.json | 48 ++++++------- .../javascript/switch-statement.json | 52 +++++++------- .../javascript/template-string.json | 48 ++++++------- .../diff-summaries/javascript/ternary.json | 52 +++++++------- .../javascript/this-expression.json | 52 +++++++------- .../javascript/throw-statement.json | 48 ++++++------- .../diff-summaries/javascript/true.json | 52 +++++++------- .../javascript/try-statement.json | 52 +++++++------- .../javascript/type-operator.json | 48 ++++++------- .../diff-summaries/javascript/undefined.json | 52 +++++++------- .../javascript/var-declaration.json | 72 +++++++++---------- .../diff-summaries/javascript/variable.json | 48 ++++++------- .../javascript/void-operator.json | 48 ++++++------- .../javascript/while-statement.json | 52 +++++++------- test/corpus/repos/javascript | 2 +- 59 files changed, 1475 insertions(+), 1475 deletions(-) diff --git a/test/corpus/diff-summaries/javascript/anonymous-function.json b/test/corpus/diff-summaries/javascript/anonymous-function.json index c2334311a..71d3aaff7 100644 --- a/test/corpus/diff-summaries/javascript/anonymous-function.json +++ b/test/corpus/diff-summaries/javascript/anonymous-function.json @@ -5,7 +5,7 @@ "anonymous-function.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -27,9 +27,9 @@ "filePaths": [ "anonymous-function.js" ], - "sha1": "2f014a3eddb509376944a4938ace7c0eb952308d", + "sha1": "b4b200a6398403b141e5fd87506899af661b97a6", "gitDir": "test/corpus/repos/javascript", - "sha2": "a8fcbf2e63b9096c5fea21b0811bc0017e48a5b5" + "sha2": "8a39270e274dfce45be0134070ed337077a22812" } ,{ "testCaseDescription": "javascript-anonymous-function-replacement-insert-test", @@ -38,7 +38,7 @@ "anonymous-function.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -55,7 +55,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 1 @@ -77,9 +77,9 @@ "filePaths": [ "anonymous-function.js" ], - "sha1": "a8fcbf2e63b9096c5fea21b0811bc0017e48a5b5", + "sha1": "8a39270e274dfce45be0134070ed337077a22812", "gitDir": "test/corpus/repos/javascript", - "sha2": "9f454c8396c898ded02c426f24bb578fde429fda" + "sha2": "0d7f05ae9912519348e739c2dd350509ece5bfd6" } ,{ "testCaseDescription": "javascript-anonymous-function-delete-insert-test", @@ -88,7 +88,7 @@ "anonymous-function.js": [ { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -118,7 +118,7 @@ }, { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -148,7 +148,7 @@ }, { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -178,7 +178,7 @@ }, { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -213,9 +213,9 @@ "filePaths": [ "anonymous-function.js" ], - "sha1": "9f454c8396c898ded02c426f24bb578fde429fda", + "sha1": "0d7f05ae9912519348e739c2dd350509ece5bfd6", "gitDir": "test/corpus/repos/javascript", - "sha2": "76497977ea3f866b200735314c4cd3d3f869d592" + "sha2": "f0269043db13f7333a5f2633fc30ff94c7321846" } ,{ "testCaseDescription": "javascript-anonymous-function-replacement-test", @@ -224,7 +224,7 @@ "anonymous-function.js": [ { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -254,7 +254,7 @@ }, { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -284,7 +284,7 @@ }, { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -314,7 +314,7 @@ }, { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -349,9 +349,9 @@ "filePaths": [ "anonymous-function.js" ], - "sha1": "76497977ea3f866b200735314c4cd3d3f869d592", + "sha1": "f0269043db13f7333a5f2633fc30ff94c7321846", "gitDir": "test/corpus/repos/javascript", - "sha2": "7e5e1a029d13f2b597d893a9238798d2be3fe2e7" + "sha2": "3d445ebd82f990df87119eb1b00223e23be72ec5" } ,{ "testCaseDescription": "javascript-anonymous-function-delete-replacement-test", @@ -360,7 +360,7 @@ "anonymous-function.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -377,7 +377,7 @@ }, { "span": { - "this": { + "delete": { "start": [ 2, 1 @@ -394,7 +394,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 1 @@ -416,9 +416,9 @@ "filePaths": [ "anonymous-function.js" ], - "sha1": "7e5e1a029d13f2b597d893a9238798d2be3fe2e7", + "sha1": "3d445ebd82f990df87119eb1b00223e23be72ec5", "gitDir": "test/corpus/repos/javascript", - "sha2": "b45156e4dd71a0fa4fa8593967953f50792c4c4e" + "sha2": "25bca4ac08d3f6ffba5acbecfe0cd7172d466cfe" } ,{ "testCaseDescription": "javascript-anonymous-function-delete-test", @@ -427,7 +427,7 @@ "anonymous-function.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -449,9 +449,9 @@ "filePaths": [ "anonymous-function.js" ], - "sha1": "b45156e4dd71a0fa4fa8593967953f50792c4c4e", + "sha1": "25bca4ac08d3f6ffba5acbecfe0cd7172d466cfe", "gitDir": "test/corpus/repos/javascript", - "sha2": "4707e7becd4c216977b13fcc4e1e1118baa7fc0f" + "sha2": "39a82d9ad7a0b2894c3c2be17a141e2ee5ff886c" } ,{ "testCaseDescription": "javascript-anonymous-function-delete-rest-test", @@ -460,7 +460,7 @@ "anonymous-function.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -482,7 +482,7 @@ "filePaths": [ "anonymous-function.js" ], - "sha1": "4707e7becd4c216977b13fcc4e1e1118baa7fc0f", + "sha1": "39a82d9ad7a0b2894c3c2be17a141e2ee5ff886c", "gitDir": "test/corpus/repos/javascript", - "sha2": "243878b6c3b6f74b080ea4f2188dffe5f3ca5517" + "sha2": "ab4f48bf9115a296943ba7b2304e674c7149c29d" }] diff --git a/test/corpus/diff-summaries/javascript/anonymous-parameterless-function.json b/test/corpus/diff-summaries/javascript/anonymous-parameterless-function.json index 19de8c0e6..495812b5a 100644 --- a/test/corpus/diff-summaries/javascript/anonymous-parameterless-function.json +++ b/test/corpus/diff-summaries/javascript/anonymous-parameterless-function.json @@ -5,7 +5,7 @@ "anonymous-parameterless-function.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -27,9 +27,9 @@ "filePaths": [ "anonymous-parameterless-function.js" ], - "sha1": "243878b6c3b6f74b080ea4f2188dffe5f3ca5517", + "sha1": "ab4f48bf9115a296943ba7b2304e674c7149c29d", "gitDir": "test/corpus/repos/javascript", - "sha2": "514143027c392e84ae25e96805949caab52f1561" + "sha2": "f43074bc2b6753a364b3b13cfc58818b23757002" } ,{ "testCaseDescription": "javascript-anonymous-parameterless-function-replacement-insert-test", @@ -38,7 +38,7 @@ "anonymous-parameterless-function.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -55,7 +55,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 1 @@ -77,9 +77,9 @@ "filePaths": [ "anonymous-parameterless-function.js" ], - "sha1": "514143027c392e84ae25e96805949caab52f1561", + "sha1": "f43074bc2b6753a364b3b13cfc58818b23757002", "gitDir": "test/corpus/repos/javascript", - "sha2": "b563ad1a2f183b9aa3eeaebd30a4d8b19b9a7a11" + "sha2": "26e0b2b93bae701963cdefbc3a8c5398186e19e5" } ,{ "testCaseDescription": "javascript-anonymous-parameterless-function-delete-insert-test", @@ -88,7 +88,7 @@ "anonymous-parameterless-function.js": [ { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -123,9 +123,9 @@ "filePaths": [ "anonymous-parameterless-function.js" ], - "sha1": "b563ad1a2f183b9aa3eeaebd30a4d8b19b9a7a11", + "sha1": "26e0b2b93bae701963cdefbc3a8c5398186e19e5", "gitDir": "test/corpus/repos/javascript", - "sha2": "f44fd8faf60a62826c1149b797d4c6de9758c2cb" + "sha2": "fd8dd926a95d09f8bc5ddd70f6332f70811861bd" } ,{ "testCaseDescription": "javascript-anonymous-parameterless-function-replacement-test", @@ -134,7 +134,7 @@ "anonymous-parameterless-function.js": [ { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -169,9 +169,9 @@ "filePaths": [ "anonymous-parameterless-function.js" ], - "sha1": "f44fd8faf60a62826c1149b797d4c6de9758c2cb", + "sha1": "fd8dd926a95d09f8bc5ddd70f6332f70811861bd", "gitDir": "test/corpus/repos/javascript", - "sha2": "76bb7e8592f8fced41f61f81538c202b3c5fb3df" + "sha2": "e4cf93ae56fcf34133d7e449d6d32d543f47a39e" } ,{ "testCaseDescription": "javascript-anonymous-parameterless-function-delete-replacement-test", @@ -180,7 +180,7 @@ "anonymous-parameterless-function.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -197,7 +197,7 @@ }, { "span": { - "this": { + "delete": { "start": [ 2, 1 @@ -214,7 +214,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 1 @@ -236,9 +236,9 @@ "filePaths": [ "anonymous-parameterless-function.js" ], - "sha1": "76bb7e8592f8fced41f61f81538c202b3c5fb3df", + "sha1": "e4cf93ae56fcf34133d7e449d6d32d543f47a39e", "gitDir": "test/corpus/repos/javascript", - "sha2": "bcc25dd39ebe005c0282ddea0611c7039fc70ec8" + "sha2": "91f3b9d0e7f9a84e72e0d8d85f9ae10e65ab5c75" } ,{ "testCaseDescription": "javascript-anonymous-parameterless-function-delete-test", @@ -247,7 +247,7 @@ "anonymous-parameterless-function.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -269,9 +269,9 @@ "filePaths": [ "anonymous-parameterless-function.js" ], - "sha1": "bcc25dd39ebe005c0282ddea0611c7039fc70ec8", + "sha1": "91f3b9d0e7f9a84e72e0d8d85f9ae10e65ab5c75", "gitDir": "test/corpus/repos/javascript", - "sha2": "425b3995f55840eef8727deb5c9b6bf82b47dfbe" + "sha2": "17288c5650b4e44ed2b59fa8b3832f99c88af33c" } ,{ "testCaseDescription": "javascript-anonymous-parameterless-function-delete-rest-test", @@ -280,7 +280,7 @@ "anonymous-parameterless-function.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -302,7 +302,7 @@ "filePaths": [ "anonymous-parameterless-function.js" ], - "sha1": "425b3995f55840eef8727deb5c9b6bf82b47dfbe", + "sha1": "17288c5650b4e44ed2b59fa8b3832f99c88af33c", "gitDir": "test/corpus/repos/javascript", - "sha2": "96217c240d7773372a78d2a23601a4a97459fcad" + "sha2": "613f8b8ea74085ab35b7398fe3f636eda7d63fa2" }] diff --git a/test/corpus/diff-summaries/javascript/array.json b/test/corpus/diff-summaries/javascript/array.json index 3a4a601fc..23f9e0773 100644 --- a/test/corpus/diff-summaries/javascript/array.json +++ b/test/corpus/diff-summaries/javascript/array.json @@ -5,7 +5,7 @@ "array.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -27,9 +27,9 @@ "filePaths": [ "array.js" ], - "sha1": "407eb0654feb336967cfa7e099e277590d97ea6d", + "sha1": "54c26c85b1720507e7c076553120465986fd2894", "gitDir": "test/corpus/repos/javascript", - "sha2": "96df91034072bb590ad228fdedccbd70de25ad8a" + "sha2": "f5bb66df169bf045026ba4442a4d974847db3489" } ,{ "testCaseDescription": "javascript-array-replacement-insert-test", @@ -38,7 +38,7 @@ "array.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -55,7 +55,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 1 @@ -77,9 +77,9 @@ "filePaths": [ "array.js" ], - "sha1": "96df91034072bb590ad228fdedccbd70de25ad8a", + "sha1": "f5bb66df169bf045026ba4442a4d974847db3489", "gitDir": "test/corpus/repos/javascript", - "sha2": "ba51e3698922b41ac81594e59a66d25d0a1f563c" + "sha2": "0cadc95617a4d5b8ed257445b10f7a78fcf7cf64" } ,{ "testCaseDescription": "javascript-array-delete-insert-test", @@ -88,7 +88,7 @@ "array.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 12 @@ -110,9 +110,9 @@ "filePaths": [ "array.js" ], - "sha1": "ba51e3698922b41ac81594e59a66d25d0a1f563c", + "sha1": "0cadc95617a4d5b8ed257445b10f7a78fcf7cf64", "gitDir": "test/corpus/repos/javascript", - "sha2": "9c4cdc5d327ec94d28bc7900690e4eb5ecfaa6a9" + "sha2": "5e1cd2633508c891278e8107d436c8a5814c476d" } ,{ "testCaseDescription": "javascript-array-replacement-test", @@ -121,7 +121,7 @@ "array.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 12 @@ -143,9 +143,9 @@ "filePaths": [ "array.js" ], - "sha1": "9c4cdc5d327ec94d28bc7900690e4eb5ecfaa6a9", + "sha1": "5e1cd2633508c891278e8107d436c8a5814c476d", "gitDir": "test/corpus/repos/javascript", - "sha2": "7293c965570f02a590689e502fe2b0d94614a019" + "sha2": "5dfefcf9ca75459d4f86e85cfb73f1f538770740" } ,{ "testCaseDescription": "javascript-array-delete-replacement-test", @@ -154,7 +154,7 @@ "array.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -171,7 +171,7 @@ }, { "span": { - "this": { + "delete": { "start": [ 2, 1 @@ -188,7 +188,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 1 @@ -210,9 +210,9 @@ "filePaths": [ "array.js" ], - "sha1": "7293c965570f02a590689e502fe2b0d94614a019", + "sha1": "5dfefcf9ca75459d4f86e85cfb73f1f538770740", "gitDir": "test/corpus/repos/javascript", - "sha2": "600a42656da1a28f6c013ab0e95a434f41f8d29c" + "sha2": "b8ede0fa6f522240174653fec41a06d409230f4c" } ,{ "testCaseDescription": "javascript-array-delete-test", @@ -221,7 +221,7 @@ "array.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -243,9 +243,9 @@ "filePaths": [ "array.js" ], - "sha1": "600a42656da1a28f6c013ab0e95a434f41f8d29c", + "sha1": "b8ede0fa6f522240174653fec41a06d409230f4c", "gitDir": "test/corpus/repos/javascript", - "sha2": "a6243ff3c461e4c1a6602cfc302f425189e6d9c3" + "sha2": "cdccd002f81bf773a827a1be1f2c1740ac6c5606" } ,{ "testCaseDescription": "javascript-array-delete-rest-test", @@ -254,7 +254,7 @@ "array.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -276,7 +276,7 @@ "filePaths": [ "array.js" ], - "sha1": "a6243ff3c461e4c1a6602cfc302f425189e6d9c3", + "sha1": "cdccd002f81bf773a827a1be1f2c1740ac6c5606", "gitDir": "test/corpus/repos/javascript", - "sha2": "0ee9c8e6c87189715a67160428ce11ee61012b05" + "sha2": "294584bae27cd565886c9c1064c423ab7a04e42d" }] diff --git a/test/corpus/diff-summaries/javascript/arrow-function.json b/test/corpus/diff-summaries/javascript/arrow-function.json index 0922abf21..d65aded44 100644 --- a/test/corpus/diff-summaries/javascript/arrow-function.json +++ b/test/corpus/diff-summaries/javascript/arrow-function.json @@ -5,7 +5,7 @@ "arrow-function.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -27,9 +27,9 @@ "filePaths": [ "arrow-function.js" ], - "sha1": "292d11c2e4263aedc5c5b54a527d686428f8ddd1", + "sha1": "822aeb40bb7867ac30402c6f1af8dcea662ed4fb", "gitDir": "test/corpus/repos/javascript", - "sha2": "6a7893d2e94099cd9fedb01b582e7ad4ff73e89d" + "sha2": "65025ba223fc1045c1271288840a1eca67fe0c6d" } ,{ "testCaseDescription": "javascript-arrow-function-replacement-insert-test", @@ -38,7 +38,7 @@ "arrow-function.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -55,7 +55,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 1 @@ -77,9 +77,9 @@ "filePaths": [ "arrow-function.js" ], - "sha1": "6a7893d2e94099cd9fedb01b582e7ad4ff73e89d", + "sha1": "65025ba223fc1045c1271288840a1eca67fe0c6d", "gitDir": "test/corpus/repos/javascript", - "sha2": "227e3fdb0b43676bfc752f04d14dc5c0c318f630" + "sha2": "c10fa6691cf995ebcc6d84b4ab6522f4ccfe28c1" } ,{ "testCaseDescription": "javascript-arrow-function-delete-insert-test", @@ -88,7 +88,7 @@ "arrow-function.js": [ { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -123,9 +123,9 @@ "filePaths": [ "arrow-function.js" ], - "sha1": "227e3fdb0b43676bfc752f04d14dc5c0c318f630", + "sha1": "c10fa6691cf995ebcc6d84b4ab6522f4ccfe28c1", "gitDir": "test/corpus/repos/javascript", - "sha2": "f093d99e79a285d5a41bb100fb86ff73e104d2fa" + "sha2": "a2267c8a6ed335962c12381cea182a78263e3a03" } ,{ "testCaseDescription": "javascript-arrow-function-replacement-test", @@ -134,7 +134,7 @@ "arrow-function.js": [ { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -169,9 +169,9 @@ "filePaths": [ "arrow-function.js" ], - "sha1": "f093d99e79a285d5a41bb100fb86ff73e104d2fa", + "sha1": "a2267c8a6ed335962c12381cea182a78263e3a03", "gitDir": "test/corpus/repos/javascript", - "sha2": "dfa11dd0f9237b75f84ec26830f0159b15391da9" + "sha2": "9e4a66eeb46e9a280a6f8efe417f600948b11100" } ,{ "testCaseDescription": "javascript-arrow-function-delete-replacement-test", @@ -180,7 +180,7 @@ "arrow-function.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -197,7 +197,7 @@ }, { "span": { - "this": { + "delete": { "start": [ 2, 1 @@ -214,7 +214,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 1 @@ -236,9 +236,9 @@ "filePaths": [ "arrow-function.js" ], - "sha1": "dfa11dd0f9237b75f84ec26830f0159b15391da9", + "sha1": "9e4a66eeb46e9a280a6f8efe417f600948b11100", "gitDir": "test/corpus/repos/javascript", - "sha2": "c0519b34f3408fc82a1f2baa7b7b48dbde82ead0" + "sha2": "91749e540ce622a0f38a4d2beb333b0287429c03" } ,{ "testCaseDescription": "javascript-arrow-function-delete-test", @@ -247,7 +247,7 @@ "arrow-function.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -269,9 +269,9 @@ "filePaths": [ "arrow-function.js" ], - "sha1": "c0519b34f3408fc82a1f2baa7b7b48dbde82ead0", + "sha1": "91749e540ce622a0f38a4d2beb333b0287429c03", "gitDir": "test/corpus/repos/javascript", - "sha2": "e03369240a62811722d7d08730e3302d97c22f3f" + "sha2": "30c18032df971c15b87ba03124262c4a17d80aa3" } ,{ "testCaseDescription": "javascript-arrow-function-delete-rest-test", @@ -280,7 +280,7 @@ "arrow-function.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -302,7 +302,7 @@ "filePaths": [ "arrow-function.js" ], - "sha1": "e03369240a62811722d7d08730e3302d97c22f3f", + "sha1": "30c18032df971c15b87ba03124262c4a17d80aa3", "gitDir": "test/corpus/repos/javascript", - "sha2": "ea881b604fbd6a7bff63837b413fbb2878da9525" + "sha2": "016ccc9573eb5bfe5ec52dcd5bb58239755ca8fd" }] diff --git a/test/corpus/diff-summaries/javascript/assignment.json b/test/corpus/diff-summaries/javascript/assignment.json index 682b68aa2..f3875821a 100644 --- a/test/corpus/diff-summaries/javascript/assignment.json +++ b/test/corpus/diff-summaries/javascript/assignment.json @@ -5,7 +5,7 @@ "assignment.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -27,9 +27,9 @@ "filePaths": [ "assignment.js" ], - "sha1": "031c53cff6b8f106847a7cd1da37a95d714890e3", + "sha1": "5c8734b51a5ad1b14629d6ba40597bcb713ffab0", "gitDir": "test/corpus/repos/javascript", - "sha2": "daa8f9455f1a839218f42157fedd14a1f2c0b46e" + "sha2": "337b7362f5cac47c55723909e65a5f6be893fb56" } ,{ "testCaseDescription": "javascript-assignment-replacement-insert-test", @@ -38,7 +38,7 @@ "assignment.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -55,7 +55,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 1 @@ -77,9 +77,9 @@ "filePaths": [ "assignment.js" ], - "sha1": "daa8f9455f1a839218f42157fedd14a1f2c0b46e", + "sha1": "337b7362f5cac47c55723909e65a5f6be893fb56", "gitDir": "test/corpus/repos/javascript", - "sha2": "ed425b43b199fcb3d66ac5d23b0b7dbe220ee22a" + "sha2": "f7ec281cb1fd5eed4e82f0c012db2b5dfcb6ab05" } ,{ "testCaseDescription": "javascript-assignment-delete-insert-test", @@ -88,7 +88,7 @@ "assignment.js": [ { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -123,9 +123,9 @@ "filePaths": [ "assignment.js" ], - "sha1": "ed425b43b199fcb3d66ac5d23b0b7dbe220ee22a", + "sha1": "f7ec281cb1fd5eed4e82f0c012db2b5dfcb6ab05", "gitDir": "test/corpus/repos/javascript", - "sha2": "02875f86427d5e098f12a1f4cdde1b0dd659b29a" + "sha2": "20ba6de9efb5238ddd88277e6ff00352cc51480c" } ,{ "testCaseDescription": "javascript-assignment-replacement-test", @@ -134,7 +134,7 @@ "assignment.js": [ { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -169,9 +169,9 @@ "filePaths": [ "assignment.js" ], - "sha1": "02875f86427d5e098f12a1f4cdde1b0dd659b29a", + "sha1": "20ba6de9efb5238ddd88277e6ff00352cc51480c", "gitDir": "test/corpus/repos/javascript", - "sha2": "1f6bdc70edf556ba4e826ea6711f7064a3f81c45" + "sha2": "67e1be509cad5719465e7c5735d0fade6cd9b571" } ,{ "testCaseDescription": "javascript-assignment-delete-replacement-test", @@ -180,7 +180,7 @@ "assignment.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -197,7 +197,7 @@ }, { "span": { - "this": { + "delete": { "start": [ 2, 1 @@ -214,7 +214,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 1 @@ -236,9 +236,9 @@ "filePaths": [ "assignment.js" ], - "sha1": "1f6bdc70edf556ba4e826ea6711f7064a3f81c45", + "sha1": "67e1be509cad5719465e7c5735d0fade6cd9b571", "gitDir": "test/corpus/repos/javascript", - "sha2": "58e91688ab485d4c9d359ab7a2007d718a9113d7" + "sha2": "faacec7eb75d0f64116bcd8aae7eee87a10b820b" } ,{ "testCaseDescription": "javascript-assignment-delete-test", @@ -247,7 +247,7 @@ "assignment.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -269,9 +269,9 @@ "filePaths": [ "assignment.js" ], - "sha1": "58e91688ab485d4c9d359ab7a2007d718a9113d7", + "sha1": "faacec7eb75d0f64116bcd8aae7eee87a10b820b", "gitDir": "test/corpus/repos/javascript", - "sha2": "9c4967350cb94e3ccece24679e3b6f8695d7f5ee" + "sha2": "cae8e1f9eb998f4bab6d091392b36dd4282c5a09" } ,{ "testCaseDescription": "javascript-assignment-delete-rest-test", @@ -280,7 +280,7 @@ "assignment.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -302,7 +302,7 @@ "filePaths": [ "assignment.js" ], - "sha1": "9c4967350cb94e3ccece24679e3b6f8695d7f5ee", + "sha1": "cae8e1f9eb998f4bab6d091392b36dd4282c5a09", "gitDir": "test/corpus/repos/javascript", - "sha2": "a8610d7d0057162d3dbbb845175a0fc8d993e0d6" + "sha2": "5abf5273d87f2dd381fecb3cb1da4b3205c43884" }] diff --git a/test/corpus/diff-summaries/javascript/bitwise-operator.json b/test/corpus/diff-summaries/javascript/bitwise-operator.json index 6c9511707..6b55766a6 100644 --- a/test/corpus/diff-summaries/javascript/bitwise-operator.json +++ b/test/corpus/diff-summaries/javascript/bitwise-operator.json @@ -5,7 +5,7 @@ "bitwise-operator.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -27,9 +27,9 @@ "filePaths": [ "bitwise-operator.js" ], - "sha1": "c9eeca7b41f404d72d81ffd3df9410d8c31ca047", + "sha1": "0a55bedb688b2d873dec7f8d898dcf6a7343e8bc", "gitDir": "test/corpus/repos/javascript", - "sha2": "4fc400a4eb7b1cfc1a100d9846e3710ff7c786bf" + "sha2": "c9e68c8a09b1d6620d90edffc20264f84e760aad" } ,{ "testCaseDescription": "javascript-bitwise-operator-replacement-insert-test", @@ -38,7 +38,7 @@ "bitwise-operator.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -55,7 +55,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 1 @@ -77,9 +77,9 @@ "filePaths": [ "bitwise-operator.js" ], - "sha1": "4fc400a4eb7b1cfc1a100d9846e3710ff7c786bf", + "sha1": "c9e68c8a09b1d6620d90edffc20264f84e760aad", "gitDir": "test/corpus/repos/javascript", - "sha2": "35c56ac13d2b06f705d85436d59990ea5ca702cd" + "sha2": "790495da1abb04f294dbbcb0e6d94b8f7d8ff728" } ,{ "testCaseDescription": "javascript-bitwise-operator-delete-insert-test", @@ -88,7 +88,7 @@ "bitwise-operator.js": [ { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -123,9 +123,9 @@ "filePaths": [ "bitwise-operator.js" ], - "sha1": "35c56ac13d2b06f705d85436d59990ea5ca702cd", + "sha1": "790495da1abb04f294dbbcb0e6d94b8f7d8ff728", "gitDir": "test/corpus/repos/javascript", - "sha2": "b6f9a8be0234a7634f488eee6a9fc74963f2c4cf" + "sha2": "195279d699cd8d5687b464de6cf9e73e9669d9bb" } ,{ "testCaseDescription": "javascript-bitwise-operator-replacement-test", @@ -134,7 +134,7 @@ "bitwise-operator.js": [ { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -169,9 +169,9 @@ "filePaths": [ "bitwise-operator.js" ], - "sha1": "b6f9a8be0234a7634f488eee6a9fc74963f2c4cf", + "sha1": "195279d699cd8d5687b464de6cf9e73e9669d9bb", "gitDir": "test/corpus/repos/javascript", - "sha2": "21b29fd95f13d556e369f0eb1bdf250be26d228b" + "sha2": "741ea0e0bfe434fb44bb43fcddec0d57c1715cd8" } ,{ "testCaseDescription": "javascript-bitwise-operator-delete-replacement-test", @@ -180,7 +180,7 @@ "bitwise-operator.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -197,7 +197,7 @@ }, { "span": { - "this": { + "delete": { "start": [ 2, 1 @@ -214,7 +214,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 1 @@ -236,9 +236,9 @@ "filePaths": [ "bitwise-operator.js" ], - "sha1": "21b29fd95f13d556e369f0eb1bdf250be26d228b", + "sha1": "741ea0e0bfe434fb44bb43fcddec0d57c1715cd8", "gitDir": "test/corpus/repos/javascript", - "sha2": "8b40de098783b76e489b51b0635681e66c689563" + "sha2": "4cfd45eae2864683d531ee98115336efb4df42ba" } ,{ "testCaseDescription": "javascript-bitwise-operator-delete-test", @@ -247,7 +247,7 @@ "bitwise-operator.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -269,9 +269,9 @@ "filePaths": [ "bitwise-operator.js" ], - "sha1": "8b40de098783b76e489b51b0635681e66c689563", + "sha1": "4cfd45eae2864683d531ee98115336efb4df42ba", "gitDir": "test/corpus/repos/javascript", - "sha2": "69d13307ee856916150b04403772e70780df3f68" + "sha2": "07651054734923312e1f86568b4c74588c020878" } ,{ "testCaseDescription": "javascript-bitwise-operator-delete-rest-test", @@ -280,7 +280,7 @@ "bitwise-operator.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -302,7 +302,7 @@ "filePaths": [ "bitwise-operator.js" ], - "sha1": "69d13307ee856916150b04403772e70780df3f68", + "sha1": "07651054734923312e1f86568b4c74588c020878", "gitDir": "test/corpus/repos/javascript", - "sha2": "0d4682971dbf0345afd2593f1068dc25c4cd0e84" + "sha2": "44726d92bc92a8541b8e3089ee22826fa31cdc69" }] diff --git a/test/corpus/diff-summaries/javascript/boolean-operator.json b/test/corpus/diff-summaries/javascript/boolean-operator.json index 9cf313807..911c1d0a7 100644 --- a/test/corpus/diff-summaries/javascript/boolean-operator.json +++ b/test/corpus/diff-summaries/javascript/boolean-operator.json @@ -5,7 +5,7 @@ "boolean-operator.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -27,9 +27,9 @@ "filePaths": [ "boolean-operator.js" ], - "sha1": "d8ca022a316c97349395e113ee5563dbfc64a120", + "sha1": "7e1caa9a941a609d09c734937d05d7b2414e8219", "gitDir": "test/corpus/repos/javascript", - "sha2": "8879f70952299b137792adc99277addb4dc9d8c2" + "sha2": "c0e2708f57e17a4ce2c1696e880ed30bad18ca26" } ,{ "testCaseDescription": "javascript-boolean-operator-replacement-insert-test", @@ -38,7 +38,7 @@ "boolean-operator.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -55,7 +55,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 1 @@ -77,9 +77,9 @@ "filePaths": [ "boolean-operator.js" ], - "sha1": "8879f70952299b137792adc99277addb4dc9d8c2", + "sha1": "c0e2708f57e17a4ce2c1696e880ed30bad18ca26", "gitDir": "test/corpus/repos/javascript", - "sha2": "db4908a1194a49d60ddb8e6e58a6a2f208db63b7" + "sha2": "0e87089f205a053aaba445030d07334a2f0a3c0d" } ,{ "testCaseDescription": "javascript-boolean-operator-delete-insert-test", @@ -90,9 +90,9 @@ "filePaths": [ "boolean-operator.js" ], - "sha1": "db4908a1194a49d60ddb8e6e58a6a2f208db63b7", + "sha1": "0e87089f205a053aaba445030d07334a2f0a3c0d", "gitDir": "test/corpus/repos/javascript", - "sha2": "bcdb6b772f14dadda64d51dbf62acc0f8f8ba2b8" + "sha2": "0e77f8929e9863a8750c2c783e827153e0f09ed5" } ,{ "testCaseDescription": "javascript-boolean-operator-replacement-test", @@ -103,9 +103,9 @@ "filePaths": [ "boolean-operator.js" ], - "sha1": "bcdb6b772f14dadda64d51dbf62acc0f8f8ba2b8", + "sha1": "0e77f8929e9863a8750c2c783e827153e0f09ed5", "gitDir": "test/corpus/repos/javascript", - "sha2": "ad89e401e551d28c64be54f8a25f60335e4f30cf" + "sha2": "7eb85e05ccbfe6f171137c8e5e0bd9574e4089f6" } ,{ "testCaseDescription": "javascript-boolean-operator-delete-replacement-test", @@ -114,7 +114,7 @@ "boolean-operator.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -136,9 +136,9 @@ "filePaths": [ "boolean-operator.js" ], - "sha1": "ad89e401e551d28c64be54f8a25f60335e4f30cf", + "sha1": "7eb85e05ccbfe6f171137c8e5e0bd9574e4089f6", "gitDir": "test/corpus/repos/javascript", - "sha2": "24fea035ee6cc6549225dc7975fa95a95aa1602b" + "sha2": "2c2f7fe0801ea179c43b3b4f8cdd228c792c7b79" } ,{ "testCaseDescription": "javascript-boolean-operator-delete-test", @@ -147,7 +147,7 @@ "boolean-operator.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -169,9 +169,9 @@ "filePaths": [ "boolean-operator.js" ], - "sha1": "24fea035ee6cc6549225dc7975fa95a95aa1602b", + "sha1": "2c2f7fe0801ea179c43b3b4f8cdd228c792c7b79", "gitDir": "test/corpus/repos/javascript", - "sha2": "46299e80d6554a9d56ebe1c500e941627a5e6798" + "sha2": "868176abe9d7d38af9fa93baea780e56ecbedb28" } ,{ "testCaseDescription": "javascript-boolean-operator-delete-rest-test", @@ -180,7 +180,7 @@ "boolean-operator.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -202,7 +202,7 @@ "filePaths": [ "boolean-operator.js" ], - "sha1": "46299e80d6554a9d56ebe1c500e941627a5e6798", + "sha1": "868176abe9d7d38af9fa93baea780e56ecbedb28", "gitDir": "test/corpus/repos/javascript", - "sha2": "c9eeca7b41f404d72d81ffd3df9410d8c31ca047" + "sha2": "0a55bedb688b2d873dec7f8d898dcf6a7343e8bc" }] diff --git a/test/corpus/diff-summaries/javascript/chained-callbacks.json b/test/corpus/diff-summaries/javascript/chained-callbacks.json index 4a035d49e..ce6891a72 100644 --- a/test/corpus/diff-summaries/javascript/chained-callbacks.json +++ b/test/corpus/diff-summaries/javascript/chained-callbacks.json @@ -5,7 +5,7 @@ "chained-callbacks.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -27,9 +27,9 @@ "filePaths": [ "chained-callbacks.js" ], - "sha1": "a8e5ca2f57c1c13f0d18a94196e0cafb7cbc2c39", + "sha1": "0a38cbb0dc46ccdf6a85eb82cfd1702afb266bac", "gitDir": "test/corpus/repos/javascript", - "sha2": "34242f9f044c914ae73dc24605730efb2dee3cdc" + "sha2": "f17c7e647d17c88e76157f48d58a43710d9f8d15" } ,{ "testCaseDescription": "javascript-chained-callbacks-replacement-insert-test", @@ -38,7 +38,7 @@ "chained-callbacks.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -55,7 +55,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 1 @@ -77,9 +77,9 @@ "filePaths": [ "chained-callbacks.js" ], - "sha1": "34242f9f044c914ae73dc24605730efb2dee3cdc", + "sha1": "f17c7e647d17c88e76157f48d58a43710d9f8d15", "gitDir": "test/corpus/repos/javascript", - "sha2": "e184d436519216be917d2238ff36e28ef57aa462" + "sha2": "df48ea9931d0b7596f69131680320c73080026d1" } ,{ "testCaseDescription": "javascript-chained-callbacks-delete-insert-test", @@ -88,7 +88,7 @@ "chained-callbacks.js": [ { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -118,7 +118,7 @@ }, { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -148,7 +148,7 @@ }, { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -183,9 +183,9 @@ "filePaths": [ "chained-callbacks.js" ], - "sha1": "e184d436519216be917d2238ff36e28ef57aa462", + "sha1": "df48ea9931d0b7596f69131680320c73080026d1", "gitDir": "test/corpus/repos/javascript", - "sha2": "d43987311e8c43612449d11670c9edab65f935e5" + "sha2": "27bac95cea0012c651e3ce2a835a4d8720bad48b" } ,{ "testCaseDescription": "javascript-chained-callbacks-replacement-test", @@ -194,7 +194,7 @@ "chained-callbacks.js": [ { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -224,7 +224,7 @@ }, { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -254,7 +254,7 @@ }, { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -289,9 +289,9 @@ "filePaths": [ "chained-callbacks.js" ], - "sha1": "d43987311e8c43612449d11670c9edab65f935e5", + "sha1": "27bac95cea0012c651e3ce2a835a4d8720bad48b", "gitDir": "test/corpus/repos/javascript", - "sha2": "2512d2e3685d8121ce3a83482ccd6f0e62211ba6" + "sha2": "9cea77c1d3d51605b53ac00289cee931ea1a2359" } ,{ "testCaseDescription": "javascript-chained-callbacks-delete-replacement-test", @@ -300,7 +300,7 @@ "chained-callbacks.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -317,7 +317,7 @@ }, { "span": { - "this": { + "delete": { "start": [ 2, 1 @@ -334,7 +334,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 1 @@ -356,9 +356,9 @@ "filePaths": [ "chained-callbacks.js" ], - "sha1": "2512d2e3685d8121ce3a83482ccd6f0e62211ba6", + "sha1": "9cea77c1d3d51605b53ac00289cee931ea1a2359", "gitDir": "test/corpus/repos/javascript", - "sha2": "9588d6d52f5beaf2f6d2f7191713872815b69d94" + "sha2": "c8f10bef923b07232331fa6453bf098ed1ffbe0f" } ,{ "testCaseDescription": "javascript-chained-callbacks-delete-test", @@ -367,7 +367,7 @@ "chained-callbacks.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -389,9 +389,9 @@ "filePaths": [ "chained-callbacks.js" ], - "sha1": "9588d6d52f5beaf2f6d2f7191713872815b69d94", + "sha1": "c8f10bef923b07232331fa6453bf098ed1ffbe0f", "gitDir": "test/corpus/repos/javascript", - "sha2": "269c6e87ad867ae1efcf0c64e487e506299e5c54" + "sha2": "7060c31a4c8985ec7bea937ac90a427fee943955" } ,{ "testCaseDescription": "javascript-chained-callbacks-delete-rest-test", @@ -400,7 +400,7 @@ "chained-callbacks.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -422,7 +422,7 @@ "filePaths": [ "chained-callbacks.js" ], - "sha1": "269c6e87ad867ae1efcf0c64e487e506299e5c54", + "sha1": "7060c31a4c8985ec7bea937ac90a427fee943955", "gitDir": "test/corpus/repos/javascript", - "sha2": "adef6baf8b5eef8703844039dc7001ac32c9ce46" + "sha2": "69d03ecd07566e6fa325c378815462768d32a996" }] diff --git a/test/corpus/diff-summaries/javascript/chained-property-access.json b/test/corpus/diff-summaries/javascript/chained-property-access.json index 6fc8fcb33..1c3da7126 100644 --- a/test/corpus/diff-summaries/javascript/chained-property-access.json +++ b/test/corpus/diff-summaries/javascript/chained-property-access.json @@ -5,7 +5,7 @@ "chained-property-access.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -27,9 +27,9 @@ "filePaths": [ "chained-property-access.js" ], - "sha1": "6d2a9f7093c2227f7d7eeedabf694118f5f17c73", + "sha1": "41bf287dfe63a1096787b4f7409a469d078c25b7", "gitDir": "test/corpus/repos/javascript", - "sha2": "6180716e37d5a804f5a457db154e6a10f0ca3e79" + "sha2": "bb2e9e006cd25f6252a12922b0818df7ec356ec6" } ,{ "testCaseDescription": "javascript-chained-property-access-replacement-insert-test", @@ -38,7 +38,7 @@ "chained-property-access.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -55,7 +55,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 1 @@ -77,9 +77,9 @@ "filePaths": [ "chained-property-access.js" ], - "sha1": "6180716e37d5a804f5a457db154e6a10f0ca3e79", + "sha1": "bb2e9e006cd25f6252a12922b0818df7ec356ec6", "gitDir": "test/corpus/repos/javascript", - "sha2": "374c46575fecedbe061db087d3705eb484b2421d" + "sha2": "31fbee39c50df203b0073b27882592050176fa9f" } ,{ "testCaseDescription": "javascript-chained-property-access-delete-insert-test", @@ -88,7 +88,7 @@ "chained-property-access.js": [ { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -118,7 +118,7 @@ }, { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -153,9 +153,9 @@ "filePaths": [ "chained-property-access.js" ], - "sha1": "374c46575fecedbe061db087d3705eb484b2421d", + "sha1": "31fbee39c50df203b0073b27882592050176fa9f", "gitDir": "test/corpus/repos/javascript", - "sha2": "85b45ee758c2258e476e829548c7e37f53487548" + "sha2": "72a5d1937c1b757cb84f78854fd3c47f3eced7f3" } ,{ "testCaseDescription": "javascript-chained-property-access-replacement-test", @@ -164,7 +164,7 @@ "chained-property-access.js": [ { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -194,7 +194,7 @@ }, { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -229,9 +229,9 @@ "filePaths": [ "chained-property-access.js" ], - "sha1": "85b45ee758c2258e476e829548c7e37f53487548", + "sha1": "72a5d1937c1b757cb84f78854fd3c47f3eced7f3", "gitDir": "test/corpus/repos/javascript", - "sha2": "bd643c48bcf421ba799eeeefd97935683be59576" + "sha2": "0ce34c376e1ce69ad7f72639e51fb3a2c0e0c182" } ,{ "testCaseDescription": "javascript-chained-property-access-delete-replacement-test", @@ -240,7 +240,7 @@ "chained-property-access.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -257,7 +257,7 @@ }, { "span": { - "this": { + "delete": { "start": [ 2, 1 @@ -274,7 +274,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 1 @@ -296,9 +296,9 @@ "filePaths": [ "chained-property-access.js" ], - "sha1": "bd643c48bcf421ba799eeeefd97935683be59576", + "sha1": "0ce34c376e1ce69ad7f72639e51fb3a2c0e0c182", "gitDir": "test/corpus/repos/javascript", - "sha2": "d2ed72cd988fc73a9658725e3e2abd2a5da1d9c2" + "sha2": "5a32624882255d98a4708e2cf87c30a64b405b4f" } ,{ "testCaseDescription": "javascript-chained-property-access-delete-test", @@ -307,7 +307,7 @@ "chained-property-access.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -329,9 +329,9 @@ "filePaths": [ "chained-property-access.js" ], - "sha1": "d2ed72cd988fc73a9658725e3e2abd2a5da1d9c2", + "sha1": "5a32624882255d98a4708e2cf87c30a64b405b4f", "gitDir": "test/corpus/repos/javascript", - "sha2": "fcf5600c10a36f83f8eb92b778c651e4cd5e4347" + "sha2": "0902995588a5793f287b8aab2a3657a6ec1fbcdc" } ,{ "testCaseDescription": "javascript-chained-property-access-delete-rest-test", @@ -340,7 +340,7 @@ "chained-property-access.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -362,7 +362,7 @@ "filePaths": [ "chained-property-access.js" ], - "sha1": "fcf5600c10a36f83f8eb92b778c651e4cd5e4347", + "sha1": "0902995588a5793f287b8aab2a3657a6ec1fbcdc", "gitDir": "test/corpus/repos/javascript", - "sha2": "a8e5ca2f57c1c13f0d18a94196e0cafb7cbc2c39" + "sha2": "0a38cbb0dc46ccdf6a85eb82cfd1702afb266bac" }] diff --git a/test/corpus/diff-summaries/javascript/class.json b/test/corpus/diff-summaries/javascript/class.json index c5679f3c8..26cdd043e 100644 --- a/test/corpus/diff-summaries/javascript/class.json +++ b/test/corpus/diff-summaries/javascript/class.json @@ -5,7 +5,7 @@ "class.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -27,9 +27,9 @@ "filePaths": [ "class.js" ], - "sha1": "83627007e919d5e812d83d6d96953a00e81369c0", + "sha1": "2a461fb53b242f9515049235816a7a7b018ed3d7", "gitDir": "test/corpus/repos/javascript", - "sha2": "d767c58b76e3cbfe7f864b591ca6c84e8f6e2927" + "sha2": "dddabcf5ab7dbc40c842a749eb8e46a1de6b57bb" } ,{ "testCaseDescription": "javascript-class-replacement-insert-test", @@ -38,7 +38,7 @@ "class.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -55,7 +55,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 1 @@ -77,9 +77,9 @@ "filePaths": [ "class.js" ], - "sha1": "d767c58b76e3cbfe7f864b591ca6c84e8f6e2927", + "sha1": "dddabcf5ab7dbc40c842a749eb8e46a1de6b57bb", "gitDir": "test/corpus/repos/javascript", - "sha2": "a651a0b93739f2b5e8386dfd512b74ddffe3a18a" + "sha2": "a1fc66c039e65c787ba76b0f53e475bd3b185c29" } ,{ "testCaseDescription": "javascript-class-delete-insert-test", @@ -88,7 +88,7 @@ "class.js": [ { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -118,7 +118,7 @@ }, { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -148,7 +148,7 @@ }, { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -183,9 +183,9 @@ "filePaths": [ "class.js" ], - "sha1": "a651a0b93739f2b5e8386dfd512b74ddffe3a18a", + "sha1": "a1fc66c039e65c787ba76b0f53e475bd3b185c29", "gitDir": "test/corpus/repos/javascript", - "sha2": "041316ee304f230e5fa4ef596e509cb0fd40eb1f" + "sha2": "e50409c326c15ea435bd958f942068f85890cd88" } ,{ "testCaseDescription": "javascript-class-replacement-test", @@ -194,7 +194,7 @@ "class.js": [ { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -224,7 +224,7 @@ }, { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -254,7 +254,7 @@ }, { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -289,9 +289,9 @@ "filePaths": [ "class.js" ], - "sha1": "041316ee304f230e5fa4ef596e509cb0fd40eb1f", + "sha1": "e50409c326c15ea435bd958f942068f85890cd88", "gitDir": "test/corpus/repos/javascript", - "sha2": "72ad8365d1dd791d49623878ff63f6efc63ee3e5" + "sha2": "48709d8e52b535873dc17daa85dde24d4375ca24" } ,{ "testCaseDescription": "javascript-class-delete-replacement-test", @@ -300,7 +300,7 @@ "class.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -317,7 +317,7 @@ }, { "span": { - "this": { + "delete": { "start": [ 2, 1 @@ -334,7 +334,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 1 @@ -356,9 +356,9 @@ "filePaths": [ "class.js" ], - "sha1": "72ad8365d1dd791d49623878ff63f6efc63ee3e5", + "sha1": "48709d8e52b535873dc17daa85dde24d4375ca24", "gitDir": "test/corpus/repos/javascript", - "sha2": "fa5b9e801beb4242d38b1fcbf3180997d5cd141c" + "sha2": "e6e1d37e807c2fc0cb28a9df20f8dc3dbaeb575b" } ,{ "testCaseDescription": "javascript-class-delete-test", @@ -367,7 +367,7 @@ "class.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -389,9 +389,9 @@ "filePaths": [ "class.js" ], - "sha1": "fa5b9e801beb4242d38b1fcbf3180997d5cd141c", + "sha1": "e6e1d37e807c2fc0cb28a9df20f8dc3dbaeb575b", "gitDir": "test/corpus/repos/javascript", - "sha2": "4d718b604febd5b0e89d62f2c32401aea6db9e94" + "sha2": "9d37c9ad21bb56f2ad789193714d422cb4a214bb" } ,{ "testCaseDescription": "javascript-class-delete-rest-test", @@ -400,7 +400,7 @@ "class.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -422,7 +422,7 @@ "filePaths": [ "class.js" ], - "sha1": "4d718b604febd5b0e89d62f2c32401aea6db9e94", + "sha1": "9d37c9ad21bb56f2ad789193714d422cb4a214bb", "gitDir": "test/corpus/repos/javascript", - "sha2": "407eb0654feb336967cfa7e099e277590d97ea6d" + "sha2": "54c26c85b1720507e7c076553120465986fd2894" }] diff --git a/test/corpus/diff-summaries/javascript/comma-operator.json b/test/corpus/diff-summaries/javascript/comma-operator.json index afd3f1d90..a423f54b3 100644 --- a/test/corpus/diff-summaries/javascript/comma-operator.json +++ b/test/corpus/diff-summaries/javascript/comma-operator.json @@ -5,7 +5,7 @@ "comma-operator.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -22,7 +22,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 1, 8 @@ -44,9 +44,9 @@ "filePaths": [ "comma-operator.js" ], - "sha1": "1cda03e29bc707037e0b55c899bc9d9fec1239db", + "sha1": "439dff969c87787fe222d1721433c8fafb0f1a89", "gitDir": "test/corpus/repos/javascript", - "sha2": "920808e907dca825300353988c74581c5ecda2ef" + "sha2": "9b1421eae5e42d1179865f793c365323e50dcf75" } ,{ "testCaseDescription": "javascript-comma-operator-replacement-insert-test", @@ -55,7 +55,7 @@ "comma-operator.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -72,7 +72,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 1 @@ -89,7 +89,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 8 @@ -111,9 +111,9 @@ "filePaths": [ "comma-operator.js" ], - "sha1": "920808e907dca825300353988c74581c5ecda2ef", + "sha1": "9b1421eae5e42d1179865f793c365323e50dcf75", "gitDir": "test/corpus/repos/javascript", - "sha2": "d3a5a9b3abd6447ccef0b274d3eb2578a33a31a7" + "sha2": "dc4d656591b9a5551f8d4eed7bcced3e77c96ced" } ,{ "testCaseDescription": "javascript-comma-operator-delete-insert-test", @@ -122,7 +122,7 @@ "comma-operator.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -139,7 +139,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 1, 8 @@ -156,7 +156,7 @@ }, { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -178,9 +178,9 @@ "filePaths": [ "comma-operator.js" ], - "sha1": "d3a5a9b3abd6447ccef0b274d3eb2578a33a31a7", + "sha1": "dc4d656591b9a5551f8d4eed7bcced3e77c96ced", "gitDir": "test/corpus/repos/javascript", - "sha2": "5596ae83228451e6923a17ab6c04643cd6cec60e" + "sha2": "c44075bf65a6c67bb986ddba4014f966f5ed6cf3" } ,{ "testCaseDescription": "javascript-comma-operator-replacement-test", @@ -189,7 +189,7 @@ "comma-operator.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -206,7 +206,7 @@ }, { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -223,7 +223,7 @@ }, { "span": { - "this": { + "delete": { "start": [ 1, 8 @@ -245,9 +245,9 @@ "filePaths": [ "comma-operator.js" ], - "sha1": "5596ae83228451e6923a17ab6c04643cd6cec60e", + "sha1": "c44075bf65a6c67bb986ddba4014f966f5ed6cf3", "gitDir": "test/corpus/repos/javascript", - "sha2": "abffc326e31c8e683d638e33541c98e6a3a2d45b" + "sha2": "bc41fdf79f37384007f19a2bf95b6bc49bacd024" } ,{ "testCaseDescription": "javascript-comma-operator-delete-replacement-test", @@ -256,7 +256,7 @@ "comma-operator.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -273,7 +273,7 @@ }, { "span": { - "this": { + "delete": { "start": [ 2, 1 @@ -290,7 +290,7 @@ }, { "span": { - "this": { + "delete": { "start": [ 2, 8 @@ -307,7 +307,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 1 @@ -329,9 +329,9 @@ "filePaths": [ "comma-operator.js" ], - "sha1": "abffc326e31c8e683d638e33541c98e6a3a2d45b", + "sha1": "bc41fdf79f37384007f19a2bf95b6bc49bacd024", "gitDir": "test/corpus/repos/javascript", - "sha2": "a5e093ceccbeb8a3a19bc72aa15bdc8bd228a291" + "sha2": "c07faa49cd9c2089755489d8f4b576a8f171de03" } ,{ "testCaseDescription": "javascript-comma-operator-delete-test", @@ -340,7 +340,7 @@ "comma-operator.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -357,7 +357,7 @@ }, { "span": { - "this": { + "delete": { "start": [ 1, 8 @@ -379,9 +379,9 @@ "filePaths": [ "comma-operator.js" ], - "sha1": "a5e093ceccbeb8a3a19bc72aa15bdc8bd228a291", + "sha1": "c07faa49cd9c2089755489d8f4b576a8f171de03", "gitDir": "test/corpus/repos/javascript", - "sha2": "4ceb6b816b56136ad1ee95bddf17552371937425" + "sha2": "d48db63fb39e2dfe3cd592fc59edc4933d74b289" } ,{ "testCaseDescription": "javascript-comma-operator-delete-rest-test", @@ -390,7 +390,7 @@ "comma-operator.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -412,7 +412,7 @@ "filePaths": [ "comma-operator.js" ], - "sha1": "4ceb6b816b56136ad1ee95bddf17552371937425", + "sha1": "d48db63fb39e2dfe3cd592fc59edc4933d74b289", "gitDir": "test/corpus/repos/javascript", - "sha2": "216c9ba07743064780c37d5f07af95a9dee2bf96" + "sha2": "62499db349bd96eba99a785f67d473de8d5b99e6" }] diff --git a/test/corpus/diff-summaries/javascript/comment.json b/test/corpus/diff-summaries/javascript/comment.json index 00ca1e6aa..959ebcf84 100644 --- a/test/corpus/diff-summaries/javascript/comment.json +++ b/test/corpus/diff-summaries/javascript/comment.json @@ -5,7 +5,7 @@ "comment.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -27,9 +27,9 @@ "filePaths": [ "comment.js" ], - "sha1": "72fe137f23a68d773c76719f790807ead00ef84a", + "sha1": "7c4be6139148ad009e9bf49df1952b9abe45aee0", "gitDir": "test/corpus/repos/javascript", - "sha2": "e5586684ed84dd036c71083544925f5230281b6f" + "sha2": "58661d0321373ae169d680373f5abeaa9edaf526" } ,{ "testCaseDescription": "javascript-comment-replacement-insert-test", @@ -38,7 +38,7 @@ "comment.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -55,7 +55,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 4, 1 @@ -77,9 +77,9 @@ "filePaths": [ "comment.js" ], - "sha1": "e5586684ed84dd036c71083544925f5230281b6f", + "sha1": "58661d0321373ae169d680373f5abeaa9edaf526", "gitDir": "test/corpus/repos/javascript", - "sha2": "7555438a387aedf7944f925ea199c6feec2ddf69" + "sha2": "6eea53ca3e63db2b8073403ee4dd76fc280d650c" } ,{ "testCaseDescription": "javascript-comment-delete-insert-test", @@ -88,7 +88,7 @@ "comment.js": [ { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -123,9 +123,9 @@ "filePaths": [ "comment.js" ], - "sha1": "7555438a387aedf7944f925ea199c6feec2ddf69", + "sha1": "6eea53ca3e63db2b8073403ee4dd76fc280d650c", "gitDir": "test/corpus/repos/javascript", - "sha2": "e6271149f264d81f8cf188641f7f75b36ba477f9" + "sha2": "8fbe23ec43ee1b6b4275658522fed08ca021f0ea" } ,{ "testCaseDescription": "javascript-comment-replacement-test", @@ -134,7 +134,7 @@ "comment.js": [ { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -169,9 +169,9 @@ "filePaths": [ "comment.js" ], - "sha1": "e6271149f264d81f8cf188641f7f75b36ba477f9", + "sha1": "8fbe23ec43ee1b6b4275658522fed08ca021f0ea", "gitDir": "test/corpus/repos/javascript", - "sha2": "103e537a1240bdeaeb6b28663f43daacbd1cd824" + "sha2": "95f13e0e9465d96342006bb4704235cc74661270" } ,{ "testCaseDescription": "javascript-comment-delete-replacement-test", @@ -180,7 +180,7 @@ "comment.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -197,7 +197,7 @@ }, { "span": { - "this": { + "delete": { "start": [ 4, 1 @@ -214,7 +214,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 1 @@ -236,9 +236,9 @@ "filePaths": [ "comment.js" ], - "sha1": "103e537a1240bdeaeb6b28663f43daacbd1cd824", + "sha1": "95f13e0e9465d96342006bb4704235cc74661270", "gitDir": "test/corpus/repos/javascript", - "sha2": "073a2a8ff5f61ca471f2b8152207301fb0583d3c" + "sha2": "5b92ecdf3967f913ce0e5463eeda1f886ea0ea9f" } ,{ "testCaseDescription": "javascript-comment-delete-test", @@ -247,7 +247,7 @@ "comment.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -269,9 +269,9 @@ "filePaths": [ "comment.js" ], - "sha1": "073a2a8ff5f61ca471f2b8152207301fb0583d3c", + "sha1": "5b92ecdf3967f913ce0e5463eeda1f886ea0ea9f", "gitDir": "test/corpus/repos/javascript", - "sha2": "cac56c3383233f34fe16d2427d319aac5f4ef1e8" + "sha2": "66a2757872c04101d7068896951e5125ae93a2b2" } ,{ "testCaseDescription": "javascript-comment-delete-rest-test", @@ -280,7 +280,7 @@ "comment.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -302,7 +302,7 @@ "filePaths": [ "comment.js" ], - "sha1": "cac56c3383233f34fe16d2427d319aac5f4ef1e8", + "sha1": "66a2757872c04101d7068896951e5125ae93a2b2", "gitDir": "test/corpus/repos/javascript", - "sha2": "ebc2ca02f6b0c4744e33e2d191158cc7f2b19a60" + "sha2": "011a5d6edc417ef0abbfb325ad08abdb917f4184" }] diff --git a/test/corpus/diff-summaries/javascript/constructor-call.json b/test/corpus/diff-summaries/javascript/constructor-call.json index 1e7825b8f..5e91677e8 100644 --- a/test/corpus/diff-summaries/javascript/constructor-call.json +++ b/test/corpus/diff-summaries/javascript/constructor-call.json @@ -5,7 +5,7 @@ "constructor-call.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -27,9 +27,9 @@ "filePaths": [ "constructor-call.js" ], - "sha1": "143f944ead8b453c8d4f2a24f35b6e64406217ff", + "sha1": "2ad39701c647bc8063509309d3cc04d0c6adf0e8", "gitDir": "test/corpus/repos/javascript", - "sha2": "b3866e0ac05a545a76032b23956be2d3b5696048" + "sha2": "5114d1974e68a6eb9a6826a3f7135c9c62ed3e6b" } ,{ "testCaseDescription": "javascript-constructor-call-replacement-insert-test", @@ -38,7 +38,7 @@ "constructor-call.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -55,7 +55,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 1 @@ -77,9 +77,9 @@ "filePaths": [ "constructor-call.js" ], - "sha1": "b3866e0ac05a545a76032b23956be2d3b5696048", + "sha1": "5114d1974e68a6eb9a6826a3f7135c9c62ed3e6b", "gitDir": "test/corpus/repos/javascript", - "sha2": "70242b1d9ffec4b1fb5115d2d3885e6b1e6bb0ae" + "sha2": "5663c1423deefd3baaf595257ed0bf2d40a914c0" } ,{ "testCaseDescription": "javascript-constructor-call-delete-insert-test", @@ -88,7 +88,7 @@ "constructor-call.js": [ { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -123,9 +123,9 @@ "filePaths": [ "constructor-call.js" ], - "sha1": "70242b1d9ffec4b1fb5115d2d3885e6b1e6bb0ae", + "sha1": "5663c1423deefd3baaf595257ed0bf2d40a914c0", "gitDir": "test/corpus/repos/javascript", - "sha2": "c4c78ad8c80317bea2ec53f28821e4af48c0bd88" + "sha2": "7fc56a50d01d51c2e5317da1199db6d4917bd76e" } ,{ "testCaseDescription": "javascript-constructor-call-replacement-test", @@ -134,7 +134,7 @@ "constructor-call.js": [ { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -169,9 +169,9 @@ "filePaths": [ "constructor-call.js" ], - "sha1": "c4c78ad8c80317bea2ec53f28821e4af48c0bd88", + "sha1": "7fc56a50d01d51c2e5317da1199db6d4917bd76e", "gitDir": "test/corpus/repos/javascript", - "sha2": "1f1239540c4737ef3f6a04878602bd5a8148e645" + "sha2": "076dec34cc2e402d97eb7f28c2167e1425168ca2" } ,{ "testCaseDescription": "javascript-constructor-call-delete-replacement-test", @@ -180,7 +180,7 @@ "constructor-call.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -197,7 +197,7 @@ }, { "span": { - "this": { + "delete": { "start": [ 2, 1 @@ -214,7 +214,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 1 @@ -236,9 +236,9 @@ "filePaths": [ "constructor-call.js" ], - "sha1": "1f1239540c4737ef3f6a04878602bd5a8148e645", + "sha1": "076dec34cc2e402d97eb7f28c2167e1425168ca2", "gitDir": "test/corpus/repos/javascript", - "sha2": "2884df62a12b83d784761b5cce876be58939a5c5" + "sha2": "53aeb6fee431b481021c69c3e9c59733ad171da6" } ,{ "testCaseDescription": "javascript-constructor-call-delete-test", @@ -247,7 +247,7 @@ "constructor-call.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -269,9 +269,9 @@ "filePaths": [ "constructor-call.js" ], - "sha1": "2884df62a12b83d784761b5cce876be58939a5c5", + "sha1": "53aeb6fee431b481021c69c3e9c59733ad171da6", "gitDir": "test/corpus/repos/javascript", - "sha2": "0151a1ccd7bd4e96dbf6ab51cbb8ef5259f9d58d" + "sha2": "030f395167154c094dba05ae435468a795ff7ecb" } ,{ "testCaseDescription": "javascript-constructor-call-delete-rest-test", @@ -280,7 +280,7 @@ "constructor-call.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -302,7 +302,7 @@ "filePaths": [ "constructor-call.js" ], - "sha1": "0151a1ccd7bd4e96dbf6ab51cbb8ef5259f9d58d", + "sha1": "030f395167154c094dba05ae435468a795ff7ecb", "gitDir": "test/corpus/repos/javascript", - "sha2": "29d3dd029a42aa320f2d154af468cc33e9fc7be2" + "sha2": "ebf93ce214fd99b995fc859da2c899eaf98b003a" }] diff --git a/test/corpus/diff-summaries/javascript/delete-operator.json b/test/corpus/diff-summaries/javascript/delete-operator.json index 86467c2ae..23df7b0d9 100644 --- a/test/corpus/diff-summaries/javascript/delete-operator.json +++ b/test/corpus/diff-summaries/javascript/delete-operator.json @@ -5,7 +5,7 @@ "delete-operator.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -27,9 +27,9 @@ "filePaths": [ "delete-operator.js" ], - "sha1": "215414e0397973e2f7d49a8edff9cf1d84fad02a", + "sha1": "ba1f4c979646df1521e9a187cc24c8b8afc3cd24", "gitDir": "test/corpus/repos/javascript", - "sha2": "d8c710fa6ec1bc818d5abd0e03a3396c962cbf09" + "sha2": "22b408a5efa333a6a8d9eb9221c6d158da79b97a" } ,{ "testCaseDescription": "javascript-delete-operator-replacement-insert-test", @@ -38,7 +38,7 @@ "delete-operator.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -55,7 +55,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 1 @@ -77,9 +77,9 @@ "filePaths": [ "delete-operator.js" ], - "sha1": "d8c710fa6ec1bc818d5abd0e03a3396c962cbf09", + "sha1": "22b408a5efa333a6a8d9eb9221c6d158da79b97a", "gitDir": "test/corpus/repos/javascript", - "sha2": "ea533b83665a30a88932b4eeb27cb010d5da3e62" + "sha2": "c8bb0986f68e4a877c005a52b97594cf548cf60a" } ,{ "testCaseDescription": "javascript-delete-operator-delete-insert-test", @@ -88,7 +88,7 @@ "delete-operator.js": [ { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -123,9 +123,9 @@ "filePaths": [ "delete-operator.js" ], - "sha1": "ea533b83665a30a88932b4eeb27cb010d5da3e62", + "sha1": "c8bb0986f68e4a877c005a52b97594cf548cf60a", "gitDir": "test/corpus/repos/javascript", - "sha2": "76af60d9b2739cd60803165c951a06f1f43b28d6" + "sha2": "4616b0eb947d61ab5f859fcd16067da2f6d73c10" } ,{ "testCaseDescription": "javascript-delete-operator-replacement-test", @@ -134,7 +134,7 @@ "delete-operator.js": [ { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -169,9 +169,9 @@ "filePaths": [ "delete-operator.js" ], - "sha1": "76af60d9b2739cd60803165c951a06f1f43b28d6", + "sha1": "4616b0eb947d61ab5f859fcd16067da2f6d73c10", "gitDir": "test/corpus/repos/javascript", - "sha2": "c5d56aba0a3f9250ea6694fb8b69e665e108fcff" + "sha2": "bdd2a3aa22441e4f32c6423cca49f16b1003caaf" } ,{ "testCaseDescription": "javascript-delete-operator-delete-replacement-test", @@ -180,7 +180,7 @@ "delete-operator.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -197,7 +197,7 @@ }, { "span": { - "this": { + "delete": { "start": [ 2, 1 @@ -214,7 +214,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 1 @@ -236,9 +236,9 @@ "filePaths": [ "delete-operator.js" ], - "sha1": "c5d56aba0a3f9250ea6694fb8b69e665e108fcff", + "sha1": "bdd2a3aa22441e4f32c6423cca49f16b1003caaf", "gitDir": "test/corpus/repos/javascript", - "sha2": "f84b7f615724f057da0b037ba8942ca64baca215" + "sha2": "58411bd05b3352bcc84f5d298a003cd1dfac51db" } ,{ "testCaseDescription": "javascript-delete-operator-delete-test", @@ -247,7 +247,7 @@ "delete-operator.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -269,9 +269,9 @@ "filePaths": [ "delete-operator.js" ], - "sha1": "f84b7f615724f057da0b037ba8942ca64baca215", + "sha1": "58411bd05b3352bcc84f5d298a003cd1dfac51db", "gitDir": "test/corpus/repos/javascript", - "sha2": "f5ecaefd1ea1a6aab1fe3b87edade118bc047069" + "sha2": "f6400b281b3ff58773e3fcc1e7cd8ceafef368d3" } ,{ "testCaseDescription": "javascript-delete-operator-delete-rest-test", @@ -280,7 +280,7 @@ "delete-operator.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -302,7 +302,7 @@ "filePaths": [ "delete-operator.js" ], - "sha1": "f5ecaefd1ea1a6aab1fe3b87edade118bc047069", + "sha1": "f6400b281b3ff58773e3fcc1e7cd8ceafef368d3", "gitDir": "test/corpus/repos/javascript", - "sha2": "9dd33ff948d47044417ab8a6cb2dd82903a8a1b4" + "sha2": "9b9215fdd0036d2a74bfc6a6c4b43187e3ad3ef8" }] diff --git a/test/corpus/diff-summaries/javascript/do-while-statement.json b/test/corpus/diff-summaries/javascript/do-while-statement.json index cebbb0a7e..11cc885e8 100644 --- a/test/corpus/diff-summaries/javascript/do-while-statement.json +++ b/test/corpus/diff-summaries/javascript/do-while-statement.json @@ -5,7 +5,7 @@ "do-while-statement.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -27,9 +27,9 @@ "filePaths": [ "do-while-statement.js" ], - "sha1": "b9bce32850180705594c7350911bd0714243f188", + "sha1": "101c947313c24c2e76769c572c080adea44c80da", "gitDir": "test/corpus/repos/javascript", - "sha2": "feb124cab094dde09b565be6f2996a9718b336a1" + "sha2": "93936ed87065031f73b74f8be77314335ecd7cd9" } ,{ "testCaseDescription": "javascript-do-while-statement-replacement-insert-test", @@ -38,7 +38,7 @@ "do-while-statement.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -55,7 +55,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 1 @@ -77,9 +77,9 @@ "filePaths": [ "do-while-statement.js" ], - "sha1": "feb124cab094dde09b565be6f2996a9718b336a1", + "sha1": "93936ed87065031f73b74f8be77314335ecd7cd9", "gitDir": "test/corpus/repos/javascript", - "sha2": "67aa4101b8d9063a8392ac374f99552ced02dcf5" + "sha2": "e9de7cb5a587ed02a47bcd9fab126ec64929f1aa" } ,{ "testCaseDescription": "javascript-do-while-statement-delete-insert-test", @@ -88,7 +88,7 @@ "do-while-statement.js": [ { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -118,7 +118,7 @@ }, { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -153,9 +153,9 @@ "filePaths": [ "do-while-statement.js" ], - "sha1": "67aa4101b8d9063a8392ac374f99552ced02dcf5", + "sha1": "e9de7cb5a587ed02a47bcd9fab126ec64929f1aa", "gitDir": "test/corpus/repos/javascript", - "sha2": "47f65b68c178b04fb6235d9ace27cd4be21f882c" + "sha2": "fc875ea9de56cf36209363fbbcfba7d7f8b99a1c" } ,{ "testCaseDescription": "javascript-do-while-statement-replacement-test", @@ -164,7 +164,7 @@ "do-while-statement.js": [ { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -194,7 +194,7 @@ }, { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -229,9 +229,9 @@ "filePaths": [ "do-while-statement.js" ], - "sha1": "47f65b68c178b04fb6235d9ace27cd4be21f882c", + "sha1": "fc875ea9de56cf36209363fbbcfba7d7f8b99a1c", "gitDir": "test/corpus/repos/javascript", - "sha2": "21bd4c94aeec230846083136748043dff480d670" + "sha2": "f84c5d87ee8b4610e69f3adc8df2431ba8f49925" } ,{ "testCaseDescription": "javascript-do-while-statement-delete-replacement-test", @@ -240,7 +240,7 @@ "do-while-statement.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -257,7 +257,7 @@ }, { "span": { - "this": { + "delete": { "start": [ 2, 1 @@ -274,7 +274,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 1 @@ -296,9 +296,9 @@ "filePaths": [ "do-while-statement.js" ], - "sha1": "21bd4c94aeec230846083136748043dff480d670", + "sha1": "f84c5d87ee8b4610e69f3adc8df2431ba8f49925", "gitDir": "test/corpus/repos/javascript", - "sha2": "8c37de8d14d78dac20ddb465749f7c48e0127f1f" + "sha2": "97f785d41e9c18cc05f6448c76686f01ea910c39" } ,{ "testCaseDescription": "javascript-do-while-statement-delete-test", @@ -307,7 +307,7 @@ "do-while-statement.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -329,9 +329,9 @@ "filePaths": [ "do-while-statement.js" ], - "sha1": "8c37de8d14d78dac20ddb465749f7c48e0127f1f", + "sha1": "97f785d41e9c18cc05f6448c76686f01ea910c39", "gitDir": "test/corpus/repos/javascript", - "sha2": "b49364de77f4824a01f67f3e988806f0ad800219" + "sha2": "27f0e253d26f01785aa481b298e72590f8f193da" } ,{ "testCaseDescription": "javascript-do-while-statement-delete-rest-test", @@ -340,7 +340,7 @@ "do-while-statement.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -362,7 +362,7 @@ "filePaths": [ "do-while-statement.js" ], - "sha1": "b49364de77f4824a01f67f3e988806f0ad800219", + "sha1": "27f0e253d26f01785aa481b298e72590f8f193da", "gitDir": "test/corpus/repos/javascript", - "sha2": "ea1cb608a188b06972bcdf47db341f8b953076b1" + "sha2": "c2a48d97ae6754bf21e1dbfa2e13bde3f68deb9c" }] diff --git a/test/corpus/diff-summaries/javascript/false.json b/test/corpus/diff-summaries/javascript/false.json index 79ccd0369..ad4940d87 100644 --- a/test/corpus/diff-summaries/javascript/false.json +++ b/test/corpus/diff-summaries/javascript/false.json @@ -5,7 +5,7 @@ "false.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -27,9 +27,9 @@ "filePaths": [ "false.js" ], - "sha1": "2729ff0e359b38bda1f650d3283d4116dc2fa3ad", + "sha1": "0cad1bc8f133de3ec0a2bff083b413422673bbb7", "gitDir": "test/corpus/repos/javascript", - "sha2": "f3388f96624945060a50d25605d1391e28d228c8" + "sha2": "f4a3023cecb97a83e81f0b674de98c9f764a6057" } ,{ "testCaseDescription": "javascript-false-replacement-insert-test", @@ -38,7 +38,7 @@ "false.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -55,7 +55,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 1 @@ -77,9 +77,9 @@ "filePaths": [ "false.js" ], - "sha1": "f3388f96624945060a50d25605d1391e28d228c8", + "sha1": "f4a3023cecb97a83e81f0b674de98c9f764a6057", "gitDir": "test/corpus/repos/javascript", - "sha2": "db41deeb70100e3865202cc00e8e58aee3872cc6" + "sha2": "548d690ca10714f0a92c5a3d8fd3884b2f617088" } ,{ "testCaseDescription": "javascript-false-delete-insert-test", @@ -88,7 +88,7 @@ "false.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -105,7 +105,7 @@ }, { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -127,9 +127,9 @@ "filePaths": [ "false.js" ], - "sha1": "db41deeb70100e3865202cc00e8e58aee3872cc6", + "sha1": "548d690ca10714f0a92c5a3d8fd3884b2f617088", "gitDir": "test/corpus/repos/javascript", - "sha2": "007e522abd031d402ea364bbe7fa4794512b8831" + "sha2": "3cd2a6fd547555f9688312759b68a9dbd98418af" } ,{ "testCaseDescription": "javascript-false-replacement-test", @@ -138,7 +138,7 @@ "false.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -155,7 +155,7 @@ }, { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -177,9 +177,9 @@ "filePaths": [ "false.js" ], - "sha1": "007e522abd031d402ea364bbe7fa4794512b8831", + "sha1": "3cd2a6fd547555f9688312759b68a9dbd98418af", "gitDir": "test/corpus/repos/javascript", - "sha2": "7e20e8bcefefbd5d330dff0036879a5d61b20eaa" + "sha2": "f010b4e20d7b0b41f58b23c815ff2564ef7657e3" } ,{ "testCaseDescription": "javascript-false-delete-replacement-test", @@ -188,7 +188,7 @@ "false.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -205,7 +205,7 @@ }, { "span": { - "this": { + "delete": { "start": [ 2, 1 @@ -222,7 +222,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 1 @@ -244,9 +244,9 @@ "filePaths": [ "false.js" ], - "sha1": "7e20e8bcefefbd5d330dff0036879a5d61b20eaa", + "sha1": "f010b4e20d7b0b41f58b23c815ff2564ef7657e3", "gitDir": "test/corpus/repos/javascript", - "sha2": "b4998a49cb6282b601fe5a1c784f1f7a01353d95" + "sha2": "64b12cb4eca55960d98f1bb66c121b7f26701a0b" } ,{ "testCaseDescription": "javascript-false-delete-test", @@ -255,7 +255,7 @@ "false.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -277,9 +277,9 @@ "filePaths": [ "false.js" ], - "sha1": "b4998a49cb6282b601fe5a1c784f1f7a01353d95", + "sha1": "64b12cb4eca55960d98f1bb66c121b7f26701a0b", "gitDir": "test/corpus/repos/javascript", - "sha2": "aed8db8659025ab4f77fcadeb6fa78617942c1c1" + "sha2": "34dbc99b39acb62b2babc1773d707f87331aa6e5" } ,{ "testCaseDescription": "javascript-false-delete-rest-test", @@ -288,7 +288,7 @@ "false.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -310,7 +310,7 @@ "filePaths": [ "false.js" ], - "sha1": "aed8db8659025ab4f77fcadeb6fa78617942c1c1", + "sha1": "34dbc99b39acb62b2babc1773d707f87331aa6e5", "gitDir": "test/corpus/repos/javascript", - "sha2": "83627007e919d5e812d83d6d96953a00e81369c0" + "sha2": "2a461fb53b242f9515049235816a7a7b018ed3d7" }] diff --git a/test/corpus/diff-summaries/javascript/for-in-statement.json b/test/corpus/diff-summaries/javascript/for-in-statement.json index d135613ff..0ab172fb7 100644 --- a/test/corpus/diff-summaries/javascript/for-in-statement.json +++ b/test/corpus/diff-summaries/javascript/for-in-statement.json @@ -5,7 +5,7 @@ "for-in-statement.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -27,9 +27,9 @@ "filePaths": [ "for-in-statement.js" ], - "sha1": "67dfbd7b45236e87dcd260ea7ac3c14b307c474f", + "sha1": "17aa0b04103d8aaedf77c3ff72f699f18194a962", "gitDir": "test/corpus/repos/javascript", - "sha2": "19dc2045717a1f9514c2499039d442ab79bfd4a6" + "sha2": "e84def0e1a12e34c85dcec7af88b964eeb198e63" } ,{ "testCaseDescription": "javascript-for-in-statement-replacement-insert-test", @@ -38,7 +38,7 @@ "for-in-statement.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -55,7 +55,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 1 @@ -77,9 +77,9 @@ "filePaths": [ "for-in-statement.js" ], - "sha1": "19dc2045717a1f9514c2499039d442ab79bfd4a6", + "sha1": "e84def0e1a12e34c85dcec7af88b964eeb198e63", "gitDir": "test/corpus/repos/javascript", - "sha2": "7395f4cca91248937b82d2fc067af9df623531b2" + "sha2": "f4ea564697dda7f2cc02fe16c0879aeb5952ddc2" } ,{ "testCaseDescription": "javascript-for-in-statement-delete-insert-test", @@ -88,7 +88,7 @@ "for-in-statement.js": [ { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -118,7 +118,7 @@ }, { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -148,7 +148,7 @@ }, { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -183,9 +183,9 @@ "filePaths": [ "for-in-statement.js" ], - "sha1": "7395f4cca91248937b82d2fc067af9df623531b2", + "sha1": "f4ea564697dda7f2cc02fe16c0879aeb5952ddc2", "gitDir": "test/corpus/repos/javascript", - "sha2": "894b6a15cc88919d0447f0fac7474905e8d3a47a" + "sha2": "9e92b2178f4fec83f11e97e548ff1e4c438df489" } ,{ "testCaseDescription": "javascript-for-in-statement-replacement-test", @@ -194,7 +194,7 @@ "for-in-statement.js": [ { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -224,7 +224,7 @@ }, { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -254,7 +254,7 @@ }, { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -289,9 +289,9 @@ "filePaths": [ "for-in-statement.js" ], - "sha1": "894b6a15cc88919d0447f0fac7474905e8d3a47a", + "sha1": "9e92b2178f4fec83f11e97e548ff1e4c438df489", "gitDir": "test/corpus/repos/javascript", - "sha2": "441fa10580c23888485006cbf55fab3d45c7174a" + "sha2": "fa62d70d1bf140a2a4339ac3b0811e3bed1eb9d5" } ,{ "testCaseDescription": "javascript-for-in-statement-delete-replacement-test", @@ -300,7 +300,7 @@ "for-in-statement.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -317,7 +317,7 @@ }, { "span": { - "this": { + "delete": { "start": [ 2, 1 @@ -334,7 +334,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 1 @@ -356,9 +356,9 @@ "filePaths": [ "for-in-statement.js" ], - "sha1": "441fa10580c23888485006cbf55fab3d45c7174a", + "sha1": "fa62d70d1bf140a2a4339ac3b0811e3bed1eb9d5", "gitDir": "test/corpus/repos/javascript", - "sha2": "c0fe338eebebf02a5e8565dbd13c703b61fcba53" + "sha2": "6eb412c429997ade58d7a15e880562076bfb9517" } ,{ "testCaseDescription": "javascript-for-in-statement-delete-test", @@ -367,7 +367,7 @@ "for-in-statement.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -389,9 +389,9 @@ "filePaths": [ "for-in-statement.js" ], - "sha1": "c0fe338eebebf02a5e8565dbd13c703b61fcba53", + "sha1": "6eb412c429997ade58d7a15e880562076bfb9517", "gitDir": "test/corpus/repos/javascript", - "sha2": "0706b7a9ebeff341744499a50b6d8731ce528c28" + "sha2": "0fead3b4746ae5344c4a240e1e177146ec3ada81" } ,{ "testCaseDescription": "javascript-for-in-statement-delete-rest-test", @@ -400,7 +400,7 @@ "for-in-statement.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -422,7 +422,7 @@ "filePaths": [ "for-in-statement.js" ], - "sha1": "0706b7a9ebeff341744499a50b6d8731ce528c28", + "sha1": "0fead3b4746ae5344c4a240e1e177146ec3ada81", "gitDir": "test/corpus/repos/javascript", - "sha2": "0ce3d1634f59a931d031cceac08ce3ea5e009bcd" + "sha2": "0ae77f84b193044495c0abfc49d346bde5e39414" }] diff --git a/test/corpus/diff-summaries/javascript/for-loop-with-in-statement.json b/test/corpus/diff-summaries/javascript/for-loop-with-in-statement.json index 79bf98b52..17d54119e 100644 --- a/test/corpus/diff-summaries/javascript/for-loop-with-in-statement.json +++ b/test/corpus/diff-summaries/javascript/for-loop-with-in-statement.json @@ -5,7 +5,7 @@ "for-loop-with-in-statement.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -27,9 +27,9 @@ "filePaths": [ "for-loop-with-in-statement.js" ], - "sha1": "312b5471c29b4f453f6c99ef1d2b0192b8075191", + "sha1": "195a1d9a04af2cce44e8af09913140e80af6656f", "gitDir": "test/corpus/repos/javascript", - "sha2": "737c5203d4608c368579f6972a34df1ae804037a" + "sha2": "7d1d4882288053a383c3aa95e23e9984182f32d0" } ,{ "testCaseDescription": "javascript-for-loop-with-in-statement-replacement-insert-test", @@ -38,7 +38,7 @@ "for-loop-with-in-statement.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -55,7 +55,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 1 @@ -77,9 +77,9 @@ "filePaths": [ "for-loop-with-in-statement.js" ], - "sha1": "737c5203d4608c368579f6972a34df1ae804037a", + "sha1": "7d1d4882288053a383c3aa95e23e9984182f32d0", "gitDir": "test/corpus/repos/javascript", - "sha2": "4c777e89f1e9772f566cd5f163e9065c67eb3e59" + "sha2": "b92a7a77b05f33eb98feb0b56335dc0e9abb3eef" } ,{ "testCaseDescription": "javascript-for-loop-with-in-statement-delete-insert-test", @@ -88,7 +88,7 @@ "for-loop-with-in-statement.js": [ { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -118,7 +118,7 @@ }, { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -153,9 +153,9 @@ "filePaths": [ "for-loop-with-in-statement.js" ], - "sha1": "4c777e89f1e9772f566cd5f163e9065c67eb3e59", + "sha1": "b92a7a77b05f33eb98feb0b56335dc0e9abb3eef", "gitDir": "test/corpus/repos/javascript", - "sha2": "65a3a5c3cdd175168e8b86559dff2915718dfa82" + "sha2": "317015fd398ef080136c5200ab496ce236ec85d6" } ,{ "testCaseDescription": "javascript-for-loop-with-in-statement-replacement-test", @@ -164,7 +164,7 @@ "for-loop-with-in-statement.js": [ { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -194,7 +194,7 @@ }, { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -229,9 +229,9 @@ "filePaths": [ "for-loop-with-in-statement.js" ], - "sha1": "65a3a5c3cdd175168e8b86559dff2915718dfa82", + "sha1": "317015fd398ef080136c5200ab496ce236ec85d6", "gitDir": "test/corpus/repos/javascript", - "sha2": "75d9025eb499683a7dabdbf36451a364d19fa48b" + "sha2": "ce83a72b91d364110f8c0b19b8db6de0d7dbe799" } ,{ "testCaseDescription": "javascript-for-loop-with-in-statement-delete-replacement-test", @@ -240,7 +240,7 @@ "for-loop-with-in-statement.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -257,7 +257,7 @@ }, { "span": { - "this": { + "delete": { "start": [ 2, 1 @@ -274,7 +274,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 1 @@ -296,9 +296,9 @@ "filePaths": [ "for-loop-with-in-statement.js" ], - "sha1": "75d9025eb499683a7dabdbf36451a364d19fa48b", + "sha1": "ce83a72b91d364110f8c0b19b8db6de0d7dbe799", "gitDir": "test/corpus/repos/javascript", - "sha2": "5041bf027b4df79e923ee65f98cf74575c5bd185" + "sha2": "4172e6ed8b75daaad3d5e914b048dca9ea598557" } ,{ "testCaseDescription": "javascript-for-loop-with-in-statement-delete-test", @@ -307,7 +307,7 @@ "for-loop-with-in-statement.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -329,9 +329,9 @@ "filePaths": [ "for-loop-with-in-statement.js" ], - "sha1": "5041bf027b4df79e923ee65f98cf74575c5bd185", + "sha1": "4172e6ed8b75daaad3d5e914b048dca9ea598557", "gitDir": "test/corpus/repos/javascript", - "sha2": "8dffc803eab5d37b821f227e27ab2a628c4e79c6" + "sha2": "c9ba7b286fbdb4cb5edb69dfd845ff4f0c7ef0ec" } ,{ "testCaseDescription": "javascript-for-loop-with-in-statement-delete-rest-test", @@ -340,7 +340,7 @@ "for-loop-with-in-statement.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -362,7 +362,7 @@ "filePaths": [ "for-loop-with-in-statement.js" ], - "sha1": "8dffc803eab5d37b821f227e27ab2a628c4e79c6", + "sha1": "c9ba7b286fbdb4cb5edb69dfd845ff4f0c7ef0ec", "gitDir": "test/corpus/repos/javascript", - "sha2": "da728273440e826c2fe2b916bce916b15b943590" + "sha2": "dbba8dcf3e630c86fb6e8eddc4fc93408e550277" }] diff --git a/test/corpus/diff-summaries/javascript/for-of-statement.json b/test/corpus/diff-summaries/javascript/for-of-statement.json index 31cefdf15..4350b1a5e 100644 --- a/test/corpus/diff-summaries/javascript/for-of-statement.json +++ b/test/corpus/diff-summaries/javascript/for-of-statement.json @@ -5,7 +5,7 @@ "for-of-statement.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -27,9 +27,9 @@ "filePaths": [ "for-of-statement.js" ], - "sha1": "da728273440e826c2fe2b916bce916b15b943590", + "sha1": "dbba8dcf3e630c86fb6e8eddc4fc93408e550277", "gitDir": "test/corpus/repos/javascript", - "sha2": "7c34377494c9c6e85107ded6606d04476c2b2268" + "sha2": "e9daa8391a6b17f0fd238b55abfae4778eed9249" } ,{ "testCaseDescription": "javascript-for-of-statement-replacement-insert-test", @@ -38,7 +38,7 @@ "for-of-statement.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -55,7 +55,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 1 @@ -77,9 +77,9 @@ "filePaths": [ "for-of-statement.js" ], - "sha1": "7c34377494c9c6e85107ded6606d04476c2b2268", + "sha1": "e9daa8391a6b17f0fd238b55abfae4778eed9249", "gitDir": "test/corpus/repos/javascript", - "sha2": "826976cafe522d197bca1e54505385f9927a93df" + "sha2": "1e2381938a88e94e3f8f1cfdf6d44b24ca2cf0f4" } ,{ "testCaseDescription": "javascript-for-of-statement-delete-insert-test", @@ -88,7 +88,7 @@ "for-of-statement.js": [ { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -118,7 +118,7 @@ }, { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -148,7 +148,7 @@ }, { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -183,9 +183,9 @@ "filePaths": [ "for-of-statement.js" ], - "sha1": "826976cafe522d197bca1e54505385f9927a93df", + "sha1": "1e2381938a88e94e3f8f1cfdf6d44b24ca2cf0f4", "gitDir": "test/corpus/repos/javascript", - "sha2": "f62dd3dacb19116d9b248549e23eff65b07a94a7" + "sha2": "b6fa78c74f9e8387335a3d83ad88f4527cb90bd9" } ,{ "testCaseDescription": "javascript-for-of-statement-replacement-test", @@ -194,7 +194,7 @@ "for-of-statement.js": [ { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -224,7 +224,7 @@ }, { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -254,7 +254,7 @@ }, { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -289,9 +289,9 @@ "filePaths": [ "for-of-statement.js" ], - "sha1": "f62dd3dacb19116d9b248549e23eff65b07a94a7", + "sha1": "b6fa78c74f9e8387335a3d83ad88f4527cb90bd9", "gitDir": "test/corpus/repos/javascript", - "sha2": "65962e4817eecea21c95026afd9cb40387aaa657" + "sha2": "3486a1725bd6dae3a69b5eea6a6580838211acaa" } ,{ "testCaseDescription": "javascript-for-of-statement-delete-replacement-test", @@ -300,7 +300,7 @@ "for-of-statement.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -317,7 +317,7 @@ }, { "span": { - "this": { + "delete": { "start": [ 2, 1 @@ -334,7 +334,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 1 @@ -356,9 +356,9 @@ "filePaths": [ "for-of-statement.js" ], - "sha1": "65962e4817eecea21c95026afd9cb40387aaa657", + "sha1": "3486a1725bd6dae3a69b5eea6a6580838211acaa", "gitDir": "test/corpus/repos/javascript", - "sha2": "44a40ac1376d641124b097e8a6e1e2d9b12c991c" + "sha2": "202a08ba3f50529869723184bfa7bb7933e89a7f" } ,{ "testCaseDescription": "javascript-for-of-statement-delete-test", @@ -367,7 +367,7 @@ "for-of-statement.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -389,9 +389,9 @@ "filePaths": [ "for-of-statement.js" ], - "sha1": "44a40ac1376d641124b097e8a6e1e2d9b12c991c", + "sha1": "202a08ba3f50529869723184bfa7bb7933e89a7f", "gitDir": "test/corpus/repos/javascript", - "sha2": "c7c2ac9ea4db0fb48c75d5fbf756f4474054d0fe" + "sha2": "4a44d4b00382cfb3765b33274aeae1ca79d482f2" } ,{ "testCaseDescription": "javascript-for-of-statement-delete-rest-test", @@ -400,7 +400,7 @@ "for-of-statement.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -422,7 +422,7 @@ "filePaths": [ "for-of-statement.js" ], - "sha1": "c7c2ac9ea4db0fb48c75d5fbf756f4474054d0fe", + "sha1": "4a44d4b00382cfb3765b33274aeae1ca79d482f2", "gitDir": "test/corpus/repos/javascript", - "sha2": "7f97f2e3a13baab2548b10a72e291b71ca0b9fa4" + "sha2": "1cbcc1b45ee2afdae4047efbc3ee0f15e89e3394" }] diff --git a/test/corpus/diff-summaries/javascript/for-statement.json b/test/corpus/diff-summaries/javascript/for-statement.json index 41443f789..d91369f95 100644 --- a/test/corpus/diff-summaries/javascript/for-statement.json +++ b/test/corpus/diff-summaries/javascript/for-statement.json @@ -5,7 +5,7 @@ "for-statement.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -27,9 +27,9 @@ "filePaths": [ "for-statement.js" ], - "sha1": "b7399e257e9ce0b28ce3080ac7e8edb2778614a3", + "sha1": "af26873a60eeb28bb292941d2ee8cae7449c9a37", "gitDir": "test/corpus/repos/javascript", - "sha2": "d476b0d1ac0e6db2068623c1f59607edebcaca08" + "sha2": "4665224dffa93b74a2f0a8053558dfb93b45af47" } ,{ "testCaseDescription": "javascript-for-statement-replacement-insert-test", @@ -38,7 +38,7 @@ "for-statement.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -55,7 +55,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 1 @@ -77,9 +77,9 @@ "filePaths": [ "for-statement.js" ], - "sha1": "d476b0d1ac0e6db2068623c1f59607edebcaca08", + "sha1": "4665224dffa93b74a2f0a8053558dfb93b45af47", "gitDir": "test/corpus/repos/javascript", - "sha2": "ca52f8da99ea8e209eb129dd6d8433b56a6eee30" + "sha2": "538dc4c01c536388c10e1815483666e3af597c91" } ,{ "testCaseDescription": "javascript-for-statement-delete-insert-test", @@ -88,7 +88,7 @@ "for-statement.js": [ { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -123,9 +123,9 @@ "filePaths": [ "for-statement.js" ], - "sha1": "ca52f8da99ea8e209eb129dd6d8433b56a6eee30", + "sha1": "538dc4c01c536388c10e1815483666e3af597c91", "gitDir": "test/corpus/repos/javascript", - "sha2": "f76f9890979255661b54a280596c95f979dbeab0" + "sha2": "5391123a87a501fa3ee089ba964b2944bdb19cd4" } ,{ "testCaseDescription": "javascript-for-statement-replacement-test", @@ -134,7 +134,7 @@ "for-statement.js": [ { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -169,9 +169,9 @@ "filePaths": [ "for-statement.js" ], - "sha1": "f76f9890979255661b54a280596c95f979dbeab0", + "sha1": "5391123a87a501fa3ee089ba964b2944bdb19cd4", "gitDir": "test/corpus/repos/javascript", - "sha2": "91a63fdc213376bcf0dfb8a6d8c0ce895acdcd91" + "sha2": "df2bb1dc7f724576ce006be7fd2faac784a6ee04" } ,{ "testCaseDescription": "javascript-for-statement-delete-replacement-test", @@ -180,7 +180,7 @@ "for-statement.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -197,7 +197,7 @@ }, { "span": { - "this": { + "delete": { "start": [ 2, 1 @@ -214,7 +214,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 1 @@ -236,9 +236,9 @@ "filePaths": [ "for-statement.js" ], - "sha1": "91a63fdc213376bcf0dfb8a6d8c0ce895acdcd91", + "sha1": "df2bb1dc7f724576ce006be7fd2faac784a6ee04", "gitDir": "test/corpus/repos/javascript", - "sha2": "b8a203be1d315305a0d3e8e92700adf18f64cfb8" + "sha2": "a244106eee60395f9ffbd4a8ae799ed2df4529bf" } ,{ "testCaseDescription": "javascript-for-statement-delete-test", @@ -247,7 +247,7 @@ "for-statement.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -269,9 +269,9 @@ "filePaths": [ "for-statement.js" ], - "sha1": "b8a203be1d315305a0d3e8e92700adf18f64cfb8", + "sha1": "a244106eee60395f9ffbd4a8ae799ed2df4529bf", "gitDir": "test/corpus/repos/javascript", - "sha2": "18cdc03ac4c49a1dafaa9f510dfb157efa7967ce" + "sha2": "405664414cbd68bbe5ffa0c689fa30cc234c289f" } ,{ "testCaseDescription": "javascript-for-statement-delete-rest-test", @@ -280,7 +280,7 @@ "for-statement.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -302,7 +302,7 @@ "filePaths": [ "for-statement.js" ], - "sha1": "18cdc03ac4c49a1dafaa9f510dfb157efa7967ce", + "sha1": "405664414cbd68bbe5ffa0c689fa30cc234c289f", "gitDir": "test/corpus/repos/javascript", - "sha2": "031c53cff6b8f106847a7cd1da37a95d714890e3" + "sha2": "5c8734b51a5ad1b14629d6ba40597bcb713ffab0" }] diff --git a/test/corpus/diff-summaries/javascript/function-call-args.json b/test/corpus/diff-summaries/javascript/function-call-args.json index 0cb749ed6..953f6afeb 100644 --- a/test/corpus/diff-summaries/javascript/function-call-args.json +++ b/test/corpus/diff-summaries/javascript/function-call-args.json @@ -5,7 +5,7 @@ "function-call-args.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -27,9 +27,9 @@ "filePaths": [ "function-call-args.js" ], - "sha1": "d40eaae205d67245d41875f45a6cd12cc1c6beee", + "sha1": "c64bd8c8fddd5dfddd8b66e5da73f44196a2f949", "gitDir": "test/corpus/repos/javascript", - "sha2": "dbcc4e50275e5bd1f0511f2059f6018b692c1a9d" + "sha2": "28d158494212d7e7a8d669cfcf00cb94c469fd8a" } ,{ "testCaseDescription": "javascript-function-call-args-replacement-insert-test", @@ -38,7 +38,7 @@ "function-call-args.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -55,7 +55,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 1 @@ -77,9 +77,9 @@ "filePaths": [ "function-call-args.js" ], - "sha1": "dbcc4e50275e5bd1f0511f2059f6018b692c1a9d", + "sha1": "28d158494212d7e7a8d669cfcf00cb94c469fd8a", "gitDir": "test/corpus/repos/javascript", - "sha2": "9a93f870384dadd725f96f57760349595f4e127a" + "sha2": "fd6089792e1161e4e8250c20c114f484007c2198" } ,{ "testCaseDescription": "javascript-function-call-args-delete-insert-test", @@ -88,7 +88,7 @@ "function-call-args.js": [ { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -118,7 +118,7 @@ }, { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -148,7 +148,7 @@ }, { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -178,7 +178,7 @@ }, { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -208,7 +208,7 @@ }, { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -238,7 +238,7 @@ }, { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -273,9 +273,9 @@ "filePaths": [ "function-call-args.js" ], - "sha1": "9a93f870384dadd725f96f57760349595f4e127a", + "sha1": "fd6089792e1161e4e8250c20c114f484007c2198", "gitDir": "test/corpus/repos/javascript", - "sha2": "069e5afce34c258c628d975edbfecd34ed9d954e" + "sha2": "692db1304b7df4f8705b40d6c6db5a223ae748c1" } ,{ "testCaseDescription": "javascript-function-call-args-replacement-test", @@ -284,7 +284,7 @@ "function-call-args.js": [ { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -314,7 +314,7 @@ }, { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -344,7 +344,7 @@ }, { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -374,7 +374,7 @@ }, { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -404,7 +404,7 @@ }, { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -434,7 +434,7 @@ }, { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -469,9 +469,9 @@ "filePaths": [ "function-call-args.js" ], - "sha1": "069e5afce34c258c628d975edbfecd34ed9d954e", + "sha1": "692db1304b7df4f8705b40d6c6db5a223ae748c1", "gitDir": "test/corpus/repos/javascript", - "sha2": "139330bfd11d844cfabefefecc39fa56286b0e23" + "sha2": "292a4c61772ea003e3c6871c38b32609872890a6" } ,{ "testCaseDescription": "javascript-function-call-args-delete-replacement-test", @@ -480,7 +480,7 @@ "function-call-args.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -497,7 +497,7 @@ }, { "span": { - "this": { + "delete": { "start": [ 2, 1 @@ -514,7 +514,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 1 @@ -536,9 +536,9 @@ "filePaths": [ "function-call-args.js" ], - "sha1": "139330bfd11d844cfabefefecc39fa56286b0e23", + "sha1": "292a4c61772ea003e3c6871c38b32609872890a6", "gitDir": "test/corpus/repos/javascript", - "sha2": "75bba8bbefbc3c66e14874571923e76553675938" + "sha2": "83b196b17789937e6cd4cabc48a69f3b695da404" } ,{ "testCaseDescription": "javascript-function-call-args-delete-test", @@ -547,7 +547,7 @@ "function-call-args.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -569,9 +569,9 @@ "filePaths": [ "function-call-args.js" ], - "sha1": "75bba8bbefbc3c66e14874571923e76553675938", + "sha1": "83b196b17789937e6cd4cabc48a69f3b695da404", "gitDir": "test/corpus/repos/javascript", - "sha2": "8a50fbb89f4afe308701d23df566f1342ef25ca2" + "sha2": "5152aeeee214a3ccf900f0ac3db753f8d515e6eb" } ,{ "testCaseDescription": "javascript-function-call-args-delete-rest-test", @@ -580,7 +580,7 @@ "function-call-args.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -602,7 +602,7 @@ "filePaths": [ "function-call-args.js" ], - "sha1": "8a50fbb89f4afe308701d23df566f1342ef25ca2", + "sha1": "5152aeeee214a3ccf900f0ac3db753f8d515e6eb", "gitDir": "test/corpus/repos/javascript", - "sha2": "143f944ead8b453c8d4f2a24f35b6e64406217ff" + "sha2": "2ad39701c647bc8063509309d3cc04d0c6adf0e8" }] diff --git a/test/corpus/diff-summaries/javascript/function-call.json b/test/corpus/diff-summaries/javascript/function-call.json index 54ce23f3a..26803fb1e 100644 --- a/test/corpus/diff-summaries/javascript/function-call.json +++ b/test/corpus/diff-summaries/javascript/function-call.json @@ -5,7 +5,7 @@ "function-call.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -27,9 +27,9 @@ "filePaths": [ "function-call.js" ], - "sha1": "adef6baf8b5eef8703844039dc7001ac32c9ce46", + "sha1": "69d03ecd07566e6fa325c378815462768d32a996", "gitDir": "test/corpus/repos/javascript", - "sha2": "e4c539759e2c91c5b34dcba8f3406fd8aa0cc054" + "sha2": "5c33dfd9f5a31344ff92b13b536fab395123631f" } ,{ "testCaseDescription": "javascript-function-call-replacement-insert-test", @@ -38,7 +38,7 @@ "function-call.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -55,7 +55,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 1 @@ -77,9 +77,9 @@ "filePaths": [ "function-call.js" ], - "sha1": "e4c539759e2c91c5b34dcba8f3406fd8aa0cc054", + "sha1": "5c33dfd9f5a31344ff92b13b536fab395123631f", "gitDir": "test/corpus/repos/javascript", - "sha2": "d6eb3328bdac66cf529be27130320aeaf98970dd" + "sha2": "9b2feff82b5b2dcd66fe5eaf3370f60d301ae00f" } ,{ "testCaseDescription": "javascript-function-call-delete-insert-test", @@ -88,7 +88,7 @@ "function-call.js": [ { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -123,9 +123,9 @@ "filePaths": [ "function-call.js" ], - "sha1": "d6eb3328bdac66cf529be27130320aeaf98970dd", + "sha1": "9b2feff82b5b2dcd66fe5eaf3370f60d301ae00f", "gitDir": "test/corpus/repos/javascript", - "sha2": "7bfcd385b7161aa142a8e3fd1a2e1448d68ff613" + "sha2": "01de50c44273a20e735f5e0befe65f6373aa2edb" } ,{ "testCaseDescription": "javascript-function-call-replacement-test", @@ -134,7 +134,7 @@ "function-call.js": [ { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -169,9 +169,9 @@ "filePaths": [ "function-call.js" ], - "sha1": "7bfcd385b7161aa142a8e3fd1a2e1448d68ff613", + "sha1": "01de50c44273a20e735f5e0befe65f6373aa2edb", "gitDir": "test/corpus/repos/javascript", - "sha2": "47b274338bb9a56dd07d19a8bdc0183ce6ee12f3" + "sha2": "bcb608a5b2e2c4e887e85005f873cc884aa8aee9" } ,{ "testCaseDescription": "javascript-function-call-delete-replacement-test", @@ -180,7 +180,7 @@ "function-call.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -197,7 +197,7 @@ }, { "span": { - "this": { + "delete": { "start": [ 2, 1 @@ -214,7 +214,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 1 @@ -236,9 +236,9 @@ "filePaths": [ "function-call.js" ], - "sha1": "47b274338bb9a56dd07d19a8bdc0183ce6ee12f3", + "sha1": "bcb608a5b2e2c4e887e85005f873cc884aa8aee9", "gitDir": "test/corpus/repos/javascript", - "sha2": "8b098f878ef245b8ddba276e26cf8604ce2bd54d" + "sha2": "a8fadba8690bd1195a9d0868aa57bd19e2ee7af6" } ,{ "testCaseDescription": "javascript-function-call-delete-test", @@ -247,7 +247,7 @@ "function-call.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -269,9 +269,9 @@ "filePaths": [ "function-call.js" ], - "sha1": "8b098f878ef245b8ddba276e26cf8604ce2bd54d", + "sha1": "a8fadba8690bd1195a9d0868aa57bd19e2ee7af6", "gitDir": "test/corpus/repos/javascript", - "sha2": "97d178bec7c2a1cff159923c7e4e9626512b5f45" + "sha2": "059865b81c068f73f9ccdc584d6e9eba10a4e3c7" } ,{ "testCaseDescription": "javascript-function-call-delete-rest-test", @@ -280,7 +280,7 @@ "function-call.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -302,7 +302,7 @@ "filePaths": [ "function-call.js" ], - "sha1": "97d178bec7c2a1cff159923c7e4e9626512b5f45", + "sha1": "059865b81c068f73f9ccdc584d6e9eba10a4e3c7", "gitDir": "test/corpus/repos/javascript", - "sha2": "ec567b366ed73c0a2d60e9e3a7736db883537a4c" + "sha2": "24037753ea53b15094b5e71eef37b694a5f001fe" }] diff --git a/test/corpus/diff-summaries/javascript/function.json b/test/corpus/diff-summaries/javascript/function.json index f5b66722a..6f2d1f987 100644 --- a/test/corpus/diff-summaries/javascript/function.json +++ b/test/corpus/diff-summaries/javascript/function.json @@ -5,7 +5,7 @@ "function.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -27,9 +27,9 @@ "filePaths": [ "function.js" ], - "sha1": "0ee9c8e6c87189715a67160428ce11ee61012b05", + "sha1": "294584bae27cd565886c9c1064c423ab7a04e42d", "gitDir": "test/corpus/repos/javascript", - "sha2": "3d7a4969e8fb9d9ece8949c38a69623bfa9892e2" + "sha2": "35fb01b172ebb75cea231977f4846d85dcca0518" } ,{ "testCaseDescription": "javascript-function-replacement-insert-test", @@ -38,7 +38,7 @@ "function.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -55,7 +55,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 1 @@ -77,9 +77,9 @@ "filePaths": [ "function.js" ], - "sha1": "3d7a4969e8fb9d9ece8949c38a69623bfa9892e2", + "sha1": "35fb01b172ebb75cea231977f4846d85dcca0518", "gitDir": "test/corpus/repos/javascript", - "sha2": "61be4363b488b3f1270c51d76a861b0520d11a43" + "sha2": "d5d65c1b1c15e480ebae432562f6041c5145751b" } ,{ "testCaseDescription": "javascript-function-delete-insert-test", @@ -88,7 +88,7 @@ "function.js": [ { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -123,9 +123,9 @@ "filePaths": [ "function.js" ], - "sha1": "61be4363b488b3f1270c51d76a861b0520d11a43", + "sha1": "d5d65c1b1c15e480ebae432562f6041c5145751b", "gitDir": "test/corpus/repos/javascript", - "sha2": "5e3d0e9170ce7aa9d264d024ac81625983a7061c" + "sha2": "c9e5e8d1bd883377d9848dac828e1b64053731ad" } ,{ "testCaseDescription": "javascript-function-replacement-test", @@ -134,7 +134,7 @@ "function.js": [ { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -169,9 +169,9 @@ "filePaths": [ "function.js" ], - "sha1": "5e3d0e9170ce7aa9d264d024ac81625983a7061c", + "sha1": "c9e5e8d1bd883377d9848dac828e1b64053731ad", "gitDir": "test/corpus/repos/javascript", - "sha2": "5bd30701955a385c366e9a64f7403ed0330f688f" + "sha2": "4bca807563e9c52adbaaa810452422fd0bb48d73" } ,{ "testCaseDescription": "javascript-function-delete-replacement-test", @@ -180,7 +180,7 @@ "function.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -197,7 +197,7 @@ }, { "span": { - "this": { + "delete": { "start": [ 2, 1 @@ -214,7 +214,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 1 @@ -236,9 +236,9 @@ "filePaths": [ "function.js" ], - "sha1": "5bd30701955a385c366e9a64f7403ed0330f688f", + "sha1": "4bca807563e9c52adbaaa810452422fd0bb48d73", "gitDir": "test/corpus/repos/javascript", - "sha2": "78bd9a251692c8c72fea22b7a64540cbce201c52" + "sha2": "32efff192345ba630c43bbac21d4b63ae582b70a" } ,{ "testCaseDescription": "javascript-function-delete-test", @@ -247,7 +247,7 @@ "function.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -269,9 +269,9 @@ "filePaths": [ "function.js" ], - "sha1": "78bd9a251692c8c72fea22b7a64540cbce201c52", + "sha1": "32efff192345ba630c43bbac21d4b63ae582b70a", "gitDir": "test/corpus/repos/javascript", - "sha2": "a7ed42c65188f70e530b0c2c16307a78612a925c" + "sha2": "f76ff63edcf9f3daccae98ca8db54e3f4ef693c9" } ,{ "testCaseDescription": "javascript-function-delete-rest-test", @@ -280,7 +280,7 @@ "function.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -302,7 +302,7 @@ "filePaths": [ "function.js" ], - "sha1": "a7ed42c65188f70e530b0c2c16307a78612a925c", + "sha1": "f76ff63edcf9f3daccae98ca8db54e3f4ef693c9", "gitDir": "test/corpus/repos/javascript", - "sha2": "292d11c2e4263aedc5c5b54a527d686428f8ddd1" + "sha2": "822aeb40bb7867ac30402c6f1af8dcea662ed4fb" }] diff --git a/test/corpus/diff-summaries/javascript/generator-function.json b/test/corpus/diff-summaries/javascript/generator-function.json index da5471d31..47540797d 100644 --- a/test/corpus/diff-summaries/javascript/generator-function.json +++ b/test/corpus/diff-summaries/javascript/generator-function.json @@ -5,7 +5,7 @@ "generator-function.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -27,9 +27,9 @@ "filePaths": [ "generator-function.js" ], - "sha1": "ea881b604fbd6a7bff63837b413fbb2878da9525", + "sha1": "016ccc9573eb5bfe5ec52dcd5bb58239755ca8fd", "gitDir": "test/corpus/repos/javascript", - "sha2": "7c4756fa11806d6f8885f4de45d34547c379a06d" + "sha2": "9a733ddbec9f01fe6f4ca2fa486f2de0c530103c" } ,{ "testCaseDescription": "javascript-generator-function-replacement-insert-test", @@ -38,7 +38,7 @@ "generator-function.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -55,7 +55,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 1 @@ -77,9 +77,9 @@ "filePaths": [ "generator-function.js" ], - "sha1": "7c4756fa11806d6f8885f4de45d34547c379a06d", + "sha1": "9a733ddbec9f01fe6f4ca2fa486f2de0c530103c", "gitDir": "test/corpus/repos/javascript", - "sha2": "60487f9057321582a5566de225346fd4bc7712c5" + "sha2": "05d9fda285817a720021accf27c5c43331f2730d" } ,{ "testCaseDescription": "javascript-generator-function-delete-insert-test", @@ -88,7 +88,7 @@ "generator-function.js": [ { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -123,9 +123,9 @@ "filePaths": [ "generator-function.js" ], - "sha1": "60487f9057321582a5566de225346fd4bc7712c5", + "sha1": "05d9fda285817a720021accf27c5c43331f2730d", "gitDir": "test/corpus/repos/javascript", - "sha2": "837d5d77bc3bc5f98fd4aa68fed39b57ca5fb726" + "sha2": "fc061ab1b2ab235efb00c4f75b5a26c7d9840e8a" } ,{ "testCaseDescription": "javascript-generator-function-replacement-test", @@ -134,7 +134,7 @@ "generator-function.js": [ { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -169,9 +169,9 @@ "filePaths": [ "generator-function.js" ], - "sha1": "837d5d77bc3bc5f98fd4aa68fed39b57ca5fb726", + "sha1": "fc061ab1b2ab235efb00c4f75b5a26c7d9840e8a", "gitDir": "test/corpus/repos/javascript", - "sha2": "535bcb4bd86100564b864040688a0812943335ec" + "sha2": "e07858b1726d3d1fb57abb417cb27b06a81b54dd" } ,{ "testCaseDescription": "javascript-generator-function-delete-replacement-test", @@ -180,7 +180,7 @@ "generator-function.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -197,7 +197,7 @@ }, { "span": { - "this": { + "delete": { "start": [ 2, 1 @@ -214,7 +214,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 1 @@ -236,9 +236,9 @@ "filePaths": [ "generator-function.js" ], - "sha1": "535bcb4bd86100564b864040688a0812943335ec", + "sha1": "e07858b1726d3d1fb57abb417cb27b06a81b54dd", "gitDir": "test/corpus/repos/javascript", - "sha2": "3c2b85be7773dc10e47c51a89c9c63f9248f9b4d" + "sha2": "47daeff4491811210cb35ead5a5d0d3a4503f4b5" } ,{ "testCaseDescription": "javascript-generator-function-delete-test", @@ -247,7 +247,7 @@ "generator-function.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -269,9 +269,9 @@ "filePaths": [ "generator-function.js" ], - "sha1": "3c2b85be7773dc10e47c51a89c9c63f9248f9b4d", + "sha1": "47daeff4491811210cb35ead5a5d0d3a4503f4b5", "gitDir": "test/corpus/repos/javascript", - "sha2": "6527df68974335620c22e86b950f2af102a9cf32" + "sha2": "6e64f5e58a3df217aefde820e66413fa8e486d6d" } ,{ "testCaseDescription": "javascript-generator-function-delete-rest-test", @@ -280,7 +280,7 @@ "generator-function.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -302,7 +302,7 @@ "filePaths": [ "generator-function.js" ], - "sha1": "6527df68974335620c22e86b950f2af102a9cf32", + "sha1": "6e64f5e58a3df217aefde820e66413fa8e486d6d", "gitDir": "test/corpus/repos/javascript", - "sha2": "5921bfd9de54f2a9868741666cba1c6fb5c4487a" + "sha2": "13ebce1d1e86a542435c13c42f189fc5f63ffa80" }] diff --git a/test/corpus/diff-summaries/javascript/identifier.json b/test/corpus/diff-summaries/javascript/identifier.json index 2b3251eb9..eff69358a 100644 --- a/test/corpus/diff-summaries/javascript/identifier.json +++ b/test/corpus/diff-summaries/javascript/identifier.json @@ -5,7 +5,7 @@ "identifier.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -27,9 +27,9 @@ "filePaths": [ "identifier.js" ], - "sha1": "1917c441d2b5dc77f63539a5df1e3cd7f0df97f3", + "sha1": "e8164f9a5c7441db5367d1dee13694204e67e3ab", "gitDir": "test/corpus/repos/javascript", - "sha2": "dabf0b766bc1e9078802788c75696638b135bba4" + "sha2": "75e27ff4b3c70434eef42d3170bdb9c7a2a60c28" } ,{ "testCaseDescription": "javascript-identifier-replacement-insert-test", @@ -38,7 +38,7 @@ "identifier.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -55,7 +55,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 1 @@ -77,9 +77,9 @@ "filePaths": [ "identifier.js" ], - "sha1": "dabf0b766bc1e9078802788c75696638b135bba4", + "sha1": "75e27ff4b3c70434eef42d3170bdb9c7a2a60c28", "gitDir": "test/corpus/repos/javascript", - "sha2": "9a6ae9eaf5793972dbd956934afece901c3585de" + "sha2": "509a9a37149c0bd5c34b27441ca3ba82bd52dda5" } ,{ "testCaseDescription": "javascript-identifier-delete-insert-test", @@ -88,7 +88,7 @@ "identifier.js": [ { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -123,9 +123,9 @@ "filePaths": [ "identifier.js" ], - "sha1": "9a6ae9eaf5793972dbd956934afece901c3585de", + "sha1": "509a9a37149c0bd5c34b27441ca3ba82bd52dda5", "gitDir": "test/corpus/repos/javascript", - "sha2": "d47d4ca7f6adc50a478c132c0322581c6a97d9ba" + "sha2": "2be41e7a7f6e3a2785ef78f40060a416a23d781b" } ,{ "testCaseDescription": "javascript-identifier-replacement-test", @@ -134,7 +134,7 @@ "identifier.js": [ { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -169,9 +169,9 @@ "filePaths": [ "identifier.js" ], - "sha1": "d47d4ca7f6adc50a478c132c0322581c6a97d9ba", + "sha1": "2be41e7a7f6e3a2785ef78f40060a416a23d781b", "gitDir": "test/corpus/repos/javascript", - "sha2": "cd4983604bbfbb1d68b3c3aa269b44bb18e7ec19" + "sha2": "6f0f8d55da8aa3a8296d008487484829f7d2bf3a" } ,{ "testCaseDescription": "javascript-identifier-delete-replacement-test", @@ -180,7 +180,7 @@ "identifier.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -197,7 +197,7 @@ }, { "span": { - "this": { + "delete": { "start": [ 2, 1 @@ -214,7 +214,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 1 @@ -236,9 +236,9 @@ "filePaths": [ "identifier.js" ], - "sha1": "cd4983604bbfbb1d68b3c3aa269b44bb18e7ec19", + "sha1": "6f0f8d55da8aa3a8296d008487484829f7d2bf3a", "gitDir": "test/corpus/repos/javascript", - "sha2": "f485b85280aefcea21b662c09b093cbe8bd7235b" + "sha2": "b7213ebdf5760f71f68072eefbe4e96553daef8c" } ,{ "testCaseDescription": "javascript-identifier-delete-test", @@ -247,7 +247,7 @@ "identifier.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -269,9 +269,9 @@ "filePaths": [ "identifier.js" ], - "sha1": "f485b85280aefcea21b662c09b093cbe8bd7235b", + "sha1": "b7213ebdf5760f71f68072eefbe4e96553daef8c", "gitDir": "test/corpus/repos/javascript", - "sha2": "e88e8ecf1d1356117505cd93c05985d9d9f7309a" + "sha2": "83da588f6151bb142adfe665a6b24c76d754571c" } ,{ "testCaseDescription": "javascript-identifier-delete-rest-test", @@ -280,7 +280,7 @@ "identifier.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -302,7 +302,7 @@ "filePaths": [ "identifier.js" ], - "sha1": "e88e8ecf1d1356117505cd93c05985d9d9f7309a", + "sha1": "83da588f6151bb142adfe665a6b24c76d754571c", "gitDir": "test/corpus/repos/javascript", - "sha2": "324ef3f6d6409ee7a42609453d3259490538a470" + "sha2": "bd9d0d22b6a226d63e44c3d654b6b618571f9912" }] diff --git a/test/corpus/diff-summaries/javascript/if-else.json b/test/corpus/diff-summaries/javascript/if-else.json index 9239cdd3d..a09c40fd0 100644 --- a/test/corpus/diff-summaries/javascript/if-else.json +++ b/test/corpus/diff-summaries/javascript/if-else.json @@ -5,7 +5,7 @@ "if-else.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -27,9 +27,9 @@ "filePaths": [ "if-else.js" ], - "sha1": "3e202ca64adc48c6445568834fbe8f9105a129f0", + "sha1": "82dd9b63b3f990900cef36bee489fcaacf288d02", "gitDir": "test/corpus/repos/javascript", - "sha2": "b4bb0651e765474189de720cc0d931b95cd0e240" + "sha2": "37d6c28a2511afe06f6f8a56a347e53a02de2dc9" } ,{ "testCaseDescription": "javascript-if-else-replacement-insert-test", @@ -38,7 +38,7 @@ "if-else.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -55,7 +55,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 1 @@ -77,9 +77,9 @@ "filePaths": [ "if-else.js" ], - "sha1": "b4bb0651e765474189de720cc0d931b95cd0e240", + "sha1": "37d6c28a2511afe06f6f8a56a347e53a02de2dc9", "gitDir": "test/corpus/repos/javascript", - "sha2": "91b41d08762cdeea84327cb0239acf3d9ac40e55" + "sha2": "10d61c3c421fb02ba22b54ff983cd29459654d24" } ,{ "testCaseDescription": "javascript-if-else-delete-insert-test", @@ -88,7 +88,7 @@ "if-else.js": [ { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -123,9 +123,9 @@ "filePaths": [ "if-else.js" ], - "sha1": "91b41d08762cdeea84327cb0239acf3d9ac40e55", + "sha1": "10d61c3c421fb02ba22b54ff983cd29459654d24", "gitDir": "test/corpus/repos/javascript", - "sha2": "f067f9cc9444e7b808e9a2ad1c95f6a606410976" + "sha2": "3440c419be8b2ae978d25f259cad4815e07ab89d" } ,{ "testCaseDescription": "javascript-if-else-replacement-test", @@ -134,7 +134,7 @@ "if-else.js": [ { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -169,9 +169,9 @@ "filePaths": [ "if-else.js" ], - "sha1": "f067f9cc9444e7b808e9a2ad1c95f6a606410976", + "sha1": "3440c419be8b2ae978d25f259cad4815e07ab89d", "gitDir": "test/corpus/repos/javascript", - "sha2": "7cdbeb6a95fe9419f442056395d4d15953e92af5" + "sha2": "1e79f5288c355ba9a3f06f3ec6e7cdf73526487e" } ,{ "testCaseDescription": "javascript-if-else-delete-replacement-test", @@ -180,7 +180,7 @@ "if-else.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -197,7 +197,7 @@ }, { "span": { - "this": { + "delete": { "start": [ 2, 1 @@ -214,7 +214,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 1 @@ -236,9 +236,9 @@ "filePaths": [ "if-else.js" ], - "sha1": "7cdbeb6a95fe9419f442056395d4d15953e92af5", + "sha1": "1e79f5288c355ba9a3f06f3ec6e7cdf73526487e", "gitDir": "test/corpus/repos/javascript", - "sha2": "5347af1d2f6459c4cb958ee5bf953a89bd53acc2" + "sha2": "edc8dd3ebd0490925aed9cb346cde3ab0abe732e" } ,{ "testCaseDescription": "javascript-if-else-delete-test", @@ -247,7 +247,7 @@ "if-else.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -269,9 +269,9 @@ "filePaths": [ "if-else.js" ], - "sha1": "5347af1d2f6459c4cb958ee5bf953a89bd53acc2", + "sha1": "edc8dd3ebd0490925aed9cb346cde3ab0abe732e", "gitDir": "test/corpus/repos/javascript", - "sha2": "e02ca1db8da2f5ec33cc3e219861b5901bf8835f" + "sha2": "8a074903d8c3de5e7aa705d257ffd2f00ce3d318" } ,{ "testCaseDescription": "javascript-if-else-delete-rest-test", @@ -280,7 +280,7 @@ "if-else.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -302,7 +302,7 @@ "filePaths": [ "if-else.js" ], - "sha1": "e02ca1db8da2f5ec33cc3e219861b5901bf8835f", + "sha1": "8a074903d8c3de5e7aa705d257ffd2f00ce3d318", "gitDir": "test/corpus/repos/javascript", - "sha2": "d3aee735401b2b9c803e3d684ab3c6b96a16898f" + "sha2": "b68fd6fad9ad8bbfb5fef0b97e42bb9899f01a0e" }] diff --git a/test/corpus/diff-summaries/javascript/if.json b/test/corpus/diff-summaries/javascript/if.json index 6c13cf220..4c4e6f770 100644 --- a/test/corpus/diff-summaries/javascript/if.json +++ b/test/corpus/diff-summaries/javascript/if.json @@ -5,7 +5,7 @@ "if.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -27,9 +27,9 @@ "filePaths": [ "if.js" ], - "sha1": "f4a276fc53b44233f1996fab1c4310602ddc195f", + "sha1": "b8ad05d0253ae191a5f160e7048edd003cbfd266", "gitDir": "test/corpus/repos/javascript", - "sha2": "369c257c6424bc2c1e64361d21e746e955512d30" + "sha2": "af68a65130c39064b6b6ff086c83bb15a93c09df" } ,{ "testCaseDescription": "javascript-if-replacement-insert-test", @@ -38,7 +38,7 @@ "if.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -55,7 +55,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 1 @@ -77,9 +77,9 @@ "filePaths": [ "if.js" ], - "sha1": "369c257c6424bc2c1e64361d21e746e955512d30", + "sha1": "af68a65130c39064b6b6ff086c83bb15a93c09df", "gitDir": "test/corpus/repos/javascript", - "sha2": "c3188f36fffcd998dd94f68b15299e784dacb393" + "sha2": "ca0d3248805ea9e4a6db03283753386c1add674c" } ,{ "testCaseDescription": "javascript-if-delete-insert-test", @@ -88,7 +88,7 @@ "if.js": [ { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -123,9 +123,9 @@ "filePaths": [ "if.js" ], - "sha1": "c3188f36fffcd998dd94f68b15299e784dacb393", + "sha1": "ca0d3248805ea9e4a6db03283753386c1add674c", "gitDir": "test/corpus/repos/javascript", - "sha2": "5ca78ae7e4e1af2f0e530be56692a1845af1a8ac" + "sha2": "4449122ca03d44093b55013864f0b91ad89b34c5" } ,{ "testCaseDescription": "javascript-if-replacement-test", @@ -134,7 +134,7 @@ "if.js": [ { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -169,9 +169,9 @@ "filePaths": [ "if.js" ], - "sha1": "5ca78ae7e4e1af2f0e530be56692a1845af1a8ac", + "sha1": "4449122ca03d44093b55013864f0b91ad89b34c5", "gitDir": "test/corpus/repos/javascript", - "sha2": "0e85ea58c2ecf3ea3acdddedc1c197cac602e4fb" + "sha2": "fb678c888f2ab154619dc7b066c706fc38b3b1e6" } ,{ "testCaseDescription": "javascript-if-delete-replacement-test", @@ -180,7 +180,7 @@ "if.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -197,7 +197,7 @@ }, { "span": { - "this": { + "delete": { "start": [ 2, 1 @@ -214,7 +214,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 1 @@ -236,9 +236,9 @@ "filePaths": [ "if.js" ], - "sha1": "0e85ea58c2ecf3ea3acdddedc1c197cac602e4fb", + "sha1": "fb678c888f2ab154619dc7b066c706fc38b3b1e6", "gitDir": "test/corpus/repos/javascript", - "sha2": "568c6d8ef9e1a62c53a0bd6bebdef66dab44497a" + "sha2": "d7133bfd9d74d7aa507fdf0eef61ed38aac6e292" } ,{ "testCaseDescription": "javascript-if-delete-test", @@ -247,7 +247,7 @@ "if.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -269,9 +269,9 @@ "filePaths": [ "if.js" ], - "sha1": "568c6d8ef9e1a62c53a0bd6bebdef66dab44497a", + "sha1": "d7133bfd9d74d7aa507fdf0eef61ed38aac6e292", "gitDir": "test/corpus/repos/javascript", - "sha2": "7c8a4d7ea730fffa4e149ae4b078c77283dc6f77" + "sha2": "d46b553e4344fd4372f71aabf2b3c4592a314ee7" } ,{ "testCaseDescription": "javascript-if-delete-rest-test", @@ -280,7 +280,7 @@ "if.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -302,7 +302,7 @@ "filePaths": [ "if.js" ], - "sha1": "7c8a4d7ea730fffa4e149ae4b078c77283dc6f77", + "sha1": "d46b553e4344fd4372f71aabf2b3c4592a314ee7", "gitDir": "test/corpus/repos/javascript", - "sha2": "3e202ca64adc48c6445568834fbe8f9105a129f0" + "sha2": "82dd9b63b3f990900cef36bee489fcaacf288d02" }] diff --git a/test/corpus/diff-summaries/javascript/math-assignment-operator.json b/test/corpus/diff-summaries/javascript/math-assignment-operator.json index ea426a009..c99252887 100644 --- a/test/corpus/diff-summaries/javascript/math-assignment-operator.json +++ b/test/corpus/diff-summaries/javascript/math-assignment-operator.json @@ -5,7 +5,7 @@ "math-assignment-operator.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -27,9 +27,9 @@ "filePaths": [ "math-assignment-operator.js" ], - "sha1": "d1711a33e14ac0a6c516afdd4885511a60f6a194", + "sha1": "7a5a7e14fdfb56a4dae67672a83aceb49d90f6bf", "gitDir": "test/corpus/repos/javascript", - "sha2": "e6ca7254618b96bd13d5bf59abe523b6b7be0696" + "sha2": "2aed63ce1b4af89d4d78887777822aa729dc46ba" } ,{ "testCaseDescription": "javascript-math-assignment-operator-replacement-insert-test", @@ -38,7 +38,7 @@ "math-assignment-operator.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -55,7 +55,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 1 @@ -77,9 +77,9 @@ "filePaths": [ "math-assignment-operator.js" ], - "sha1": "e6ca7254618b96bd13d5bf59abe523b6b7be0696", + "sha1": "2aed63ce1b4af89d4d78887777822aa729dc46ba", "gitDir": "test/corpus/repos/javascript", - "sha2": "624e4b3fcc902aad7ef2a8dd187c3504b004e01d" + "sha2": "9d231bac8540a68b2ea8d7df89c0cff4e1250a4b" } ,{ "testCaseDescription": "javascript-math-assignment-operator-delete-insert-test", @@ -88,7 +88,7 @@ "math-assignment-operator.js": [ { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -123,9 +123,9 @@ "filePaths": [ "math-assignment-operator.js" ], - "sha1": "624e4b3fcc902aad7ef2a8dd187c3504b004e01d", + "sha1": "9d231bac8540a68b2ea8d7df89c0cff4e1250a4b", "gitDir": "test/corpus/repos/javascript", - "sha2": "21d4e2aa872d6526c9ec132d7aa405034c1d5b4e" + "sha2": "4b0f35714cd2b735d9228b7ecc82d9d8af8a5367" } ,{ "testCaseDescription": "javascript-math-assignment-operator-replacement-test", @@ -134,7 +134,7 @@ "math-assignment-operator.js": [ { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -169,9 +169,9 @@ "filePaths": [ "math-assignment-operator.js" ], - "sha1": "21d4e2aa872d6526c9ec132d7aa405034c1d5b4e", + "sha1": "4b0f35714cd2b735d9228b7ecc82d9d8af8a5367", "gitDir": "test/corpus/repos/javascript", - "sha2": "849e0b35b93b33918caade8c41161658008ce343" + "sha2": "b1dbceca404978015a90e1dce406759980e0dbc0" } ,{ "testCaseDescription": "javascript-math-assignment-operator-delete-replacement-test", @@ -180,7 +180,7 @@ "math-assignment-operator.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -197,7 +197,7 @@ }, { "span": { - "this": { + "delete": { "start": [ 2, 1 @@ -214,7 +214,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 1 @@ -236,9 +236,9 @@ "filePaths": [ "math-assignment-operator.js" ], - "sha1": "849e0b35b93b33918caade8c41161658008ce343", + "sha1": "b1dbceca404978015a90e1dce406759980e0dbc0", "gitDir": "test/corpus/repos/javascript", - "sha2": "381a333198f364cf59bad22b46744c406fe5b1db" + "sha2": "913db4af5c664dfbe4523f49d2fa8943022a43f8" } ,{ "testCaseDescription": "javascript-math-assignment-operator-delete-test", @@ -247,7 +247,7 @@ "math-assignment-operator.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -269,9 +269,9 @@ "filePaths": [ "math-assignment-operator.js" ], - "sha1": "381a333198f364cf59bad22b46744c406fe5b1db", + "sha1": "913db4af5c664dfbe4523f49d2fa8943022a43f8", "gitDir": "test/corpus/repos/javascript", - "sha2": "a8136c633b138aba118c5ca17cefb2ed101687cf" + "sha2": "aa754293f0b9582f1efc6990001c9706c8d1d744" } ,{ "testCaseDescription": "javascript-math-assignment-operator-delete-rest-test", @@ -280,7 +280,7 @@ "math-assignment-operator.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -302,7 +302,7 @@ "filePaths": [ "math-assignment-operator.js" ], - "sha1": "a8136c633b138aba118c5ca17cefb2ed101687cf", + "sha1": "aa754293f0b9582f1efc6990001c9706c8d1d744", "gitDir": "test/corpus/repos/javascript", - "sha2": "312b5471c29b4f453f6c99ef1d2b0192b8075191" + "sha2": "195a1d9a04af2cce44e8af09913140e80af6656f" }] diff --git a/test/corpus/diff-summaries/javascript/math-operator.json b/test/corpus/diff-summaries/javascript/math-operator.json index 5c498a74b..65fa0700a 100644 --- a/test/corpus/diff-summaries/javascript/math-operator.json +++ b/test/corpus/diff-summaries/javascript/math-operator.json @@ -5,7 +5,7 @@ "math-operator.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -27,9 +27,9 @@ "filePaths": [ "math-operator.js" ], - "sha1": "29d3dd029a42aa320f2d154af468cc33e9fc7be2", + "sha1": "ebf93ce214fd99b995fc859da2c899eaf98b003a", "gitDir": "test/corpus/repos/javascript", - "sha2": "3bcee56c9f08e47e37624d7961b7459e341435f7" + "sha2": "93f7482ed81a2888cd6137a6015ed46fa12ceb2d" } ,{ "testCaseDescription": "javascript-math-operator-replacement-insert-test", @@ -38,7 +38,7 @@ "math-operator.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -55,7 +55,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 1 @@ -77,9 +77,9 @@ "filePaths": [ "math-operator.js" ], - "sha1": "3bcee56c9f08e47e37624d7961b7459e341435f7", + "sha1": "93f7482ed81a2888cd6137a6015ed46fa12ceb2d", "gitDir": "test/corpus/repos/javascript", - "sha2": "d5ac4c9c8fa386bf983b962f242ff6eec966310b" + "sha2": "2b8502bbe9c10431c2a08133eb6180b1e27f537e" } ,{ "testCaseDescription": "javascript-math-operator-delete-insert-test", @@ -88,7 +88,7 @@ "math-operator.js": [ { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -118,7 +118,7 @@ }, { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -153,9 +153,9 @@ "filePaths": [ "math-operator.js" ], - "sha1": "d5ac4c9c8fa386bf983b962f242ff6eec966310b", + "sha1": "2b8502bbe9c10431c2a08133eb6180b1e27f537e", "gitDir": "test/corpus/repos/javascript", - "sha2": "1ac0e212164f2068e691c5a1ee4d84af9b6a7b5a" + "sha2": "123e24693808106e6533b65a31e067441dd32d78" } ,{ "testCaseDescription": "javascript-math-operator-replacement-test", @@ -164,7 +164,7 @@ "math-operator.js": [ { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -194,7 +194,7 @@ }, { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -229,9 +229,9 @@ "filePaths": [ "math-operator.js" ], - "sha1": "1ac0e212164f2068e691c5a1ee4d84af9b6a7b5a", + "sha1": "123e24693808106e6533b65a31e067441dd32d78", "gitDir": "test/corpus/repos/javascript", - "sha2": "be4676f35933afc323b26da0d809b21731d14733" + "sha2": "e44b221c2a7632162f4498cd54046476d74c39b7" } ,{ "testCaseDescription": "javascript-math-operator-delete-replacement-test", @@ -240,7 +240,7 @@ "math-operator.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -257,7 +257,7 @@ }, { "span": { - "this": { + "delete": { "start": [ 2, 1 @@ -274,7 +274,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 1 @@ -296,9 +296,9 @@ "filePaths": [ "math-operator.js" ], - "sha1": "be4676f35933afc323b26da0d809b21731d14733", + "sha1": "e44b221c2a7632162f4498cd54046476d74c39b7", "gitDir": "test/corpus/repos/javascript", - "sha2": "5d632a1a0a0356c0301d21065697fc877a75b60c" + "sha2": "12fc0e04bb901a3cd24aefbf530a5feaa7166195" } ,{ "testCaseDescription": "javascript-math-operator-delete-test", @@ -307,7 +307,7 @@ "math-operator.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -329,9 +329,9 @@ "filePaths": [ "math-operator.js" ], - "sha1": "5d632a1a0a0356c0301d21065697fc877a75b60c", + "sha1": "12fc0e04bb901a3cd24aefbf530a5feaa7166195", "gitDir": "test/corpus/repos/javascript", - "sha2": "bbbfb139a7357fa00181518d13609396add9d3f7" + "sha2": "12b777458501d39cfc9bf6eb3a223fd942fd0ecb" } ,{ "testCaseDescription": "javascript-math-operator-delete-rest-test", @@ -340,7 +340,7 @@ "math-operator.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -362,7 +362,7 @@ "filePaths": [ "math-operator.js" ], - "sha1": "bbbfb139a7357fa00181518d13609396add9d3f7", + "sha1": "12b777458501d39cfc9bf6eb3a223fd942fd0ecb", "gitDir": "test/corpus/repos/javascript", - "sha2": "d8ca022a316c97349395e113ee5563dbfc64a120" + "sha2": "7e1caa9a941a609d09c734937d05d7b2414e8219" }] diff --git a/test/corpus/diff-summaries/javascript/member-access-assignment.json b/test/corpus/diff-summaries/javascript/member-access-assignment.json index 89af555b3..bf1d009fe 100644 --- a/test/corpus/diff-summaries/javascript/member-access-assignment.json +++ b/test/corpus/diff-summaries/javascript/member-access-assignment.json @@ -5,7 +5,7 @@ "member-access-assignment.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -27,9 +27,9 @@ "filePaths": [ "member-access-assignment.js" ], - "sha1": "a8610d7d0057162d3dbbb845175a0fc8d993e0d6", + "sha1": "5abf5273d87f2dd381fecb3cb1da4b3205c43884", "gitDir": "test/corpus/repos/javascript", - "sha2": "08bbe0c2c7b34af221387f7b6e338937343d1ff7" + "sha2": "7c50ca76820e810821259114e73a62ee28d66b9f" } ,{ "testCaseDescription": "javascript-member-access-assignment-replacement-insert-test", @@ -38,7 +38,7 @@ "member-access-assignment.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -55,7 +55,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 1 @@ -77,9 +77,9 @@ "filePaths": [ "member-access-assignment.js" ], - "sha1": "08bbe0c2c7b34af221387f7b6e338937343d1ff7", + "sha1": "7c50ca76820e810821259114e73a62ee28d66b9f", "gitDir": "test/corpus/repos/javascript", - "sha2": "40cd1385fc2decff798fadd84b828eeffa386527" + "sha2": "97c06ba774b37bb505a9701e2c437da6a97ce086" } ,{ "testCaseDescription": "javascript-member-access-assignment-delete-insert-test", @@ -88,7 +88,7 @@ "member-access-assignment.js": [ { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -123,9 +123,9 @@ "filePaths": [ "member-access-assignment.js" ], - "sha1": "40cd1385fc2decff798fadd84b828eeffa386527", + "sha1": "97c06ba774b37bb505a9701e2c437da6a97ce086", "gitDir": "test/corpus/repos/javascript", - "sha2": "2e8e5c2446be9ce6284d1e43510bcf30f6be19dc" + "sha2": "0f6ba0959bef4f60fb13bed5524b7c743c4dbe32" } ,{ "testCaseDescription": "javascript-member-access-assignment-replacement-test", @@ -134,7 +134,7 @@ "member-access-assignment.js": [ { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -169,9 +169,9 @@ "filePaths": [ "member-access-assignment.js" ], - "sha1": "2e8e5c2446be9ce6284d1e43510bcf30f6be19dc", + "sha1": "0f6ba0959bef4f60fb13bed5524b7c743c4dbe32", "gitDir": "test/corpus/repos/javascript", - "sha2": "ec1d0b50ba901bb9822226a0d615ff21d49de114" + "sha2": "833009a51368a08169ab7d8c7536fbd1b62c6d5b" } ,{ "testCaseDescription": "javascript-member-access-assignment-delete-replacement-test", @@ -180,7 +180,7 @@ "member-access-assignment.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -197,7 +197,7 @@ }, { "span": { - "this": { + "delete": { "start": [ 2, 1 @@ -214,7 +214,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 1 @@ -236,9 +236,9 @@ "filePaths": [ "member-access-assignment.js" ], - "sha1": "ec1d0b50ba901bb9822226a0d615ff21d49de114", + "sha1": "833009a51368a08169ab7d8c7536fbd1b62c6d5b", "gitDir": "test/corpus/repos/javascript", - "sha2": "8240cb6b7516b74de51980e453497e3595b4e628" + "sha2": "200d9b92ea3c25078e09984d93bd07a225175af4" } ,{ "testCaseDescription": "javascript-member-access-assignment-delete-test", @@ -247,7 +247,7 @@ "member-access-assignment.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -269,9 +269,9 @@ "filePaths": [ "member-access-assignment.js" ], - "sha1": "8240cb6b7516b74de51980e453497e3595b4e628", + "sha1": "200d9b92ea3c25078e09984d93bd07a225175af4", "gitDir": "test/corpus/repos/javascript", - "sha2": "673b347c3edaa6ebd6922c7a383f39de4484aaee" + "sha2": "ee587dae30db8fb647970f12f6777db23bbad620" } ,{ "testCaseDescription": "javascript-member-access-assignment-delete-rest-test", @@ -280,7 +280,7 @@ "member-access-assignment.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -302,7 +302,7 @@ "filePaths": [ "member-access-assignment.js" ], - "sha1": "673b347c3edaa6ebd6922c7a383f39de4484aaee", + "sha1": "ee587dae30db8fb647970f12f6777db23bbad620", "gitDir": "test/corpus/repos/javascript", - "sha2": "2777fc53b2f1b0e54aead0a015db9970af0795fe" + "sha2": "e7314eba8beae9be9a34bcf91157e5e542f4b2a9" }] diff --git a/test/corpus/diff-summaries/javascript/member-access.json b/test/corpus/diff-summaries/javascript/member-access.json index 15479c963..8549b27c7 100644 --- a/test/corpus/diff-summaries/javascript/member-access.json +++ b/test/corpus/diff-summaries/javascript/member-access.json @@ -5,7 +5,7 @@ "member-access.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -27,9 +27,9 @@ "filePaths": [ "member-access.js" ], - "sha1": "0823b029fb4c9f6bd2d8197f3f0682bc2ddd5445", + "sha1": "2f07429c5135205d55550f4c64061a6ac987da17", "gitDir": "test/corpus/repos/javascript", - "sha2": "99eb938a82f85d8d01ca67c2675efa387879d9ae" + "sha2": "f88de966d0f942a55d170dbf43070e3cb3f26a3d" } ,{ "testCaseDescription": "javascript-member-access-replacement-insert-test", @@ -38,7 +38,7 @@ "member-access.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -55,7 +55,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 1 @@ -77,9 +77,9 @@ "filePaths": [ "member-access.js" ], - "sha1": "99eb938a82f85d8d01ca67c2675efa387879d9ae", + "sha1": "f88de966d0f942a55d170dbf43070e3cb3f26a3d", "gitDir": "test/corpus/repos/javascript", - "sha2": "66971fc9cba9ba2a68c662baf8b83c1e678d5d4a" + "sha2": "6b63944a02141ea5f2696bac8c40dfb972883b13" } ,{ "testCaseDescription": "javascript-member-access-delete-insert-test", @@ -88,7 +88,7 @@ "member-access.js": [ { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -123,9 +123,9 @@ "filePaths": [ "member-access.js" ], - "sha1": "66971fc9cba9ba2a68c662baf8b83c1e678d5d4a", + "sha1": "6b63944a02141ea5f2696bac8c40dfb972883b13", "gitDir": "test/corpus/repos/javascript", - "sha2": "8bc32ef87162c91be8a015740a839c006f813127" + "sha2": "46741210b901e8b9dfa87552c0adeddc7d6beab8" } ,{ "testCaseDescription": "javascript-member-access-replacement-test", @@ -134,7 +134,7 @@ "member-access.js": [ { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -169,9 +169,9 @@ "filePaths": [ "member-access.js" ], - "sha1": "8bc32ef87162c91be8a015740a839c006f813127", + "sha1": "46741210b901e8b9dfa87552c0adeddc7d6beab8", "gitDir": "test/corpus/repos/javascript", - "sha2": "b646e69ee5a6aed13e920ab08dc34933210537fd" + "sha2": "2562b652ebd9aff9aae1acc1ac1b08610ef79f40" } ,{ "testCaseDescription": "javascript-member-access-delete-replacement-test", @@ -180,7 +180,7 @@ "member-access.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -197,7 +197,7 @@ }, { "span": { - "this": { + "delete": { "start": [ 2, 1 @@ -214,7 +214,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 1 @@ -236,9 +236,9 @@ "filePaths": [ "member-access.js" ], - "sha1": "b646e69ee5a6aed13e920ab08dc34933210537fd", + "sha1": "2562b652ebd9aff9aae1acc1ac1b08610ef79f40", "gitDir": "test/corpus/repos/javascript", - "sha2": "bd8074a2d66c30b37c6a657fbe3407e9bd32fa04" + "sha2": "191e1b5188f0e9f15bd1ba61e6e608cc27bcf423" } ,{ "testCaseDescription": "javascript-member-access-delete-test", @@ -247,7 +247,7 @@ "member-access.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -269,9 +269,9 @@ "filePaths": [ "member-access.js" ], - "sha1": "bd8074a2d66c30b37c6a657fbe3407e9bd32fa04", + "sha1": "191e1b5188f0e9f15bd1ba61e6e608cc27bcf423", "gitDir": "test/corpus/repos/javascript", - "sha2": "58d7f9d9d4d795422a7c8abdae93fdf74dddaf31" + "sha2": "fc8396189b7d6d34ae7045ef2b8dc0427df6262d" } ,{ "testCaseDescription": "javascript-member-access-delete-rest-test", @@ -280,7 +280,7 @@ "member-access.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -302,7 +302,7 @@ "filePaths": [ "member-access.js" ], - "sha1": "58d7f9d9d4d795422a7c8abdae93fdf74dddaf31", + "sha1": "fc8396189b7d6d34ae7045ef2b8dc0427df6262d", "gitDir": "test/corpus/repos/javascript", - "sha2": "0c9b3b84cb49951e79891dae24edfddccbf579a1" + "sha2": "6d6d0fda6116e0504607e3b9d770f51596723212" }] diff --git a/test/corpus/diff-summaries/javascript/method-call.json b/test/corpus/diff-summaries/javascript/method-call.json index 75752c492..ac2194021 100644 --- a/test/corpus/diff-summaries/javascript/method-call.json +++ b/test/corpus/diff-summaries/javascript/method-call.json @@ -5,7 +5,7 @@ "method-call.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -27,9 +27,9 @@ "filePaths": [ "method-call.js" ], - "sha1": "ec567b366ed73c0a2d60e9e3a7736db883537a4c", + "sha1": "24037753ea53b15094b5e71eef37b694a5f001fe", "gitDir": "test/corpus/repos/javascript", - "sha2": "840b4603bd70e3aeb19603964bb4087442882b18" + "sha2": "ce88a11c4e5b2fac1008456760bec7db01ce7d90" } ,{ "testCaseDescription": "javascript-method-call-replacement-insert-test", @@ -38,7 +38,7 @@ "method-call.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -55,7 +55,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 1 @@ -77,9 +77,9 @@ "filePaths": [ "method-call.js" ], - "sha1": "840b4603bd70e3aeb19603964bb4087442882b18", + "sha1": "ce88a11c4e5b2fac1008456760bec7db01ce7d90", "gitDir": "test/corpus/repos/javascript", - "sha2": "1e74a8573a26c304e4bdc2e687a955b5ec7b4b9a" + "sha2": "b0a9c2ae55eabfec8e38071ba5e67777bdb6b711" } ,{ "testCaseDescription": "javascript-method-call-delete-insert-test", @@ -88,7 +88,7 @@ "method-call.js": [ { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -123,9 +123,9 @@ "filePaths": [ "method-call.js" ], - "sha1": "1e74a8573a26c304e4bdc2e687a955b5ec7b4b9a", + "sha1": "b0a9c2ae55eabfec8e38071ba5e67777bdb6b711", "gitDir": "test/corpus/repos/javascript", - "sha2": "447fd2cf545ddb584f7923defe1659bcbf7b7457" + "sha2": "2e3e47822227fad89d4c04fcab8864e78275580a" } ,{ "testCaseDescription": "javascript-method-call-replacement-test", @@ -134,7 +134,7 @@ "method-call.js": [ { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -169,9 +169,9 @@ "filePaths": [ "method-call.js" ], - "sha1": "447fd2cf545ddb584f7923defe1659bcbf7b7457", + "sha1": "2e3e47822227fad89d4c04fcab8864e78275580a", "gitDir": "test/corpus/repos/javascript", - "sha2": "beb6a15d9dd99a6abe9a15360a9bf11c4cb0b62d" + "sha2": "e4743cb765f3cf98961aee3379aa6e44df5d0044" } ,{ "testCaseDescription": "javascript-method-call-delete-replacement-test", @@ -180,7 +180,7 @@ "method-call.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -197,7 +197,7 @@ }, { "span": { - "this": { + "delete": { "start": [ 2, 1 @@ -214,7 +214,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 1 @@ -236,9 +236,9 @@ "filePaths": [ "method-call.js" ], - "sha1": "beb6a15d9dd99a6abe9a15360a9bf11c4cb0b62d", + "sha1": "e4743cb765f3cf98961aee3379aa6e44df5d0044", "gitDir": "test/corpus/repos/javascript", - "sha2": "bb8bafd9ca71ecc00d4a2b17f4994eafcc4a02b6" + "sha2": "7adc939f69779c818eab16bdf36f7825068ed6a9" } ,{ "testCaseDescription": "javascript-method-call-delete-test", @@ -247,7 +247,7 @@ "method-call.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -269,9 +269,9 @@ "filePaths": [ "method-call.js" ], - "sha1": "bb8bafd9ca71ecc00d4a2b17f4994eafcc4a02b6", + "sha1": "7adc939f69779c818eab16bdf36f7825068ed6a9", "gitDir": "test/corpus/repos/javascript", - "sha2": "64c5036bb60d199c3d753f5fbc67c030597daf55" + "sha2": "9c530a1b7197ec7453b5a4af0600a715768a5727" } ,{ "testCaseDescription": "javascript-method-call-delete-rest-test", @@ -280,7 +280,7 @@ "method-call.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -302,7 +302,7 @@ "filePaths": [ "method-call.js" ], - "sha1": "64c5036bb60d199c3d753f5fbc67c030597daf55", + "sha1": "9c530a1b7197ec7453b5a4af0600a715768a5727", "gitDir": "test/corpus/repos/javascript", - "sha2": "d40eaae205d67245d41875f45a6cd12cc1c6beee" + "sha2": "c64bd8c8fddd5dfddd8b66e5da73f44196a2f949" }] diff --git a/test/corpus/diff-summaries/javascript/named-function.json b/test/corpus/diff-summaries/javascript/named-function.json index a8478f7d7..98f3abc92 100644 --- a/test/corpus/diff-summaries/javascript/named-function.json +++ b/test/corpus/diff-summaries/javascript/named-function.json @@ -5,7 +5,7 @@ "named-function.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -27,9 +27,9 @@ "filePaths": [ "named-function.js" ], - "sha1": "5921bfd9de54f2a9868741666cba1c6fb5c4487a", + "sha1": "13ebce1d1e86a542435c13c42f189fc5f63ffa80", "gitDir": "test/corpus/repos/javascript", - "sha2": "ed8f5dca6d1d96ef2b296bd5df98404d1b66c897" + "sha2": "ccf7572d97487c3437622c80426357ea3cdd949c" } ,{ "testCaseDescription": "javascript-named-function-replacement-insert-test", @@ -38,7 +38,7 @@ "named-function.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -55,7 +55,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 1 @@ -77,9 +77,9 @@ "filePaths": [ "named-function.js" ], - "sha1": "ed8f5dca6d1d96ef2b296bd5df98404d1b66c897", + "sha1": "ccf7572d97487c3437622c80426357ea3cdd949c", "gitDir": "test/corpus/repos/javascript", - "sha2": "4222bcfe67238cc7af44c45f6ec0a142cfa17c67" + "sha2": "9aef777bcfa7124d354878123376adb64d0f9b86" } ,{ "testCaseDescription": "javascript-named-function-delete-insert-test", @@ -88,7 +88,7 @@ "named-function.js": [ { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -118,7 +118,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 1, 21 @@ -135,7 +135,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 1, 27 @@ -152,7 +152,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 1, 35 @@ -169,7 +169,7 @@ }, { "span": { - "this": { + "delete": { "start": [ 1, 30 @@ -191,9 +191,9 @@ "filePaths": [ "named-function.js" ], - "sha1": "4222bcfe67238cc7af44c45f6ec0a142cfa17c67", + "sha1": "9aef777bcfa7124d354878123376adb64d0f9b86", "gitDir": "test/corpus/repos/javascript", - "sha2": "bc86a7cba72eea905c0d8c44adb3b4486b0a6a82" + "sha2": "51586f5431494e95c89dbf547d91b89affe41d80" } ,{ "testCaseDescription": "javascript-named-function-replacement-test", @@ -202,7 +202,7 @@ "named-function.js": [ { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -232,7 +232,7 @@ }, { "span": { - "this": { + "delete": { "start": [ 1, 21 @@ -249,7 +249,7 @@ }, { "span": { - "this": { + "delete": { "start": [ 1, 27 @@ -266,7 +266,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 1, 30 @@ -283,7 +283,7 @@ }, { "span": { - "this": { + "delete": { "start": [ 1, 35 @@ -305,9 +305,9 @@ "filePaths": [ "named-function.js" ], - "sha1": "bc86a7cba72eea905c0d8c44adb3b4486b0a6a82", + "sha1": "51586f5431494e95c89dbf547d91b89affe41d80", "gitDir": "test/corpus/repos/javascript", - "sha2": "f966010b747f91901e7aa9baad0cc7f1b6eef9ef" + "sha2": "412499fc3980298e4426f219fc4c7728f7970a2d" } ,{ "testCaseDescription": "javascript-named-function-delete-replacement-test", @@ -316,7 +316,7 @@ "named-function.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -333,7 +333,7 @@ }, { "span": { - "this": { + "delete": { "start": [ 2, 1 @@ -350,7 +350,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 1 @@ -372,9 +372,9 @@ "filePaths": [ "named-function.js" ], - "sha1": "f966010b747f91901e7aa9baad0cc7f1b6eef9ef", + "sha1": "412499fc3980298e4426f219fc4c7728f7970a2d", "gitDir": "test/corpus/repos/javascript", - "sha2": "67fb491a47d084d91c43b668088e5dca89cc8a75" + "sha2": "808aa67a46dd08a54a9688644ad1ed7f0a787449" } ,{ "testCaseDescription": "javascript-named-function-delete-test", @@ -383,7 +383,7 @@ "named-function.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -405,9 +405,9 @@ "filePaths": [ "named-function.js" ], - "sha1": "67fb491a47d084d91c43b668088e5dca89cc8a75", + "sha1": "808aa67a46dd08a54a9688644ad1ed7f0a787449", "gitDir": "test/corpus/repos/javascript", - "sha2": "d069d29ec02721e8951777c1a746b9717e2a0385" + "sha2": "bc6a204b96bb860353491146bcf0c4adebe28f69" } ,{ "testCaseDescription": "javascript-named-function-delete-rest-test", @@ -416,7 +416,7 @@ "named-function.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -438,7 +438,7 @@ "filePaths": [ "named-function.js" ], - "sha1": "d069d29ec02721e8951777c1a746b9717e2a0385", + "sha1": "bc6a204b96bb860353491146bcf0c4adebe28f69", "gitDir": "test/corpus/repos/javascript", - "sha2": "0823b029fb4c9f6bd2d8197f3f0682bc2ddd5445" + "sha2": "2f07429c5135205d55550f4c64061a6ac987da17" }] diff --git a/test/corpus/diff-summaries/javascript/nested-functions.json b/test/corpus/diff-summaries/javascript/nested-functions.json index 74984efaf..4a0a83e99 100644 --- a/test/corpus/diff-summaries/javascript/nested-functions.json +++ b/test/corpus/diff-summaries/javascript/nested-functions.json @@ -5,7 +5,7 @@ "nested-functions.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -27,9 +27,9 @@ "filePaths": [ "nested-functions.js" ], - "sha1": "0ce3d1634f59a931d031cceac08ce3ea5e009bcd", + "sha1": "0ae77f84b193044495c0abfc49d346bde5e39414", "gitDir": "test/corpus/repos/javascript", - "sha2": "d29340565d945f1a5a9cb195bfe11aab2317b02a" + "sha2": "ef19570b8866d3b5832b07c94b679e61d4ed5a3d" } ,{ "testCaseDescription": "javascript-nested-functions-replacement-insert-test", @@ -38,7 +38,7 @@ "nested-functions.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -55,7 +55,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 1 @@ -77,9 +77,9 @@ "filePaths": [ "nested-functions.js" ], - "sha1": "d29340565d945f1a5a9cb195bfe11aab2317b02a", + "sha1": "ef19570b8866d3b5832b07c94b679e61d4ed5a3d", "gitDir": "test/corpus/repos/javascript", - "sha2": "f7bb7dcc5b7bb4d19e1e26ae694af81a2b6abab3" + "sha2": "bc194874e5e15edb201005aca9d7b8d4f711053f" } ,{ "testCaseDescription": "javascript-nested-functions-delete-insert-test", @@ -88,7 +88,7 @@ "nested-functions.js": [ { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -118,7 +118,7 @@ }, { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -153,9 +153,9 @@ "filePaths": [ "nested-functions.js" ], - "sha1": "f7bb7dcc5b7bb4d19e1e26ae694af81a2b6abab3", + "sha1": "bc194874e5e15edb201005aca9d7b8d4f711053f", "gitDir": "test/corpus/repos/javascript", - "sha2": "f7590f3a29efea3fa6955bc75a110c01ec134abe" + "sha2": "438e79efdd7784fa092f9832cc689141253b5295" } ,{ "testCaseDescription": "javascript-nested-functions-replacement-test", @@ -164,7 +164,7 @@ "nested-functions.js": [ { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -194,7 +194,7 @@ }, { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -229,9 +229,9 @@ "filePaths": [ "nested-functions.js" ], - "sha1": "f7590f3a29efea3fa6955bc75a110c01ec134abe", + "sha1": "438e79efdd7784fa092f9832cc689141253b5295", "gitDir": "test/corpus/repos/javascript", - "sha2": "a5da6040b13da745bf4a8a2a33f66eded196cbde" + "sha2": "32af107bcaea5a5ac4849198f2d6227b6015c709" } ,{ "testCaseDescription": "javascript-nested-functions-delete-replacement-test", @@ -240,7 +240,7 @@ "nested-functions.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -257,7 +257,7 @@ }, { "span": { - "this": { + "delete": { "start": [ 2, 1 @@ -274,7 +274,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 1 @@ -296,9 +296,9 @@ "filePaths": [ "nested-functions.js" ], - "sha1": "a5da6040b13da745bf4a8a2a33f66eded196cbde", + "sha1": "32af107bcaea5a5ac4849198f2d6227b6015c709", "gitDir": "test/corpus/repos/javascript", - "sha2": "0902cf79b0d1bf066d7703e6003aad6016ed93bd" + "sha2": "b547ad567b2c5018f3f02b8dcacd63e2ae8cddc5" } ,{ "testCaseDescription": "javascript-nested-functions-delete-test", @@ -307,7 +307,7 @@ "nested-functions.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -329,9 +329,9 @@ "filePaths": [ "nested-functions.js" ], - "sha1": "0902cf79b0d1bf066d7703e6003aad6016ed93bd", + "sha1": "b547ad567b2c5018f3f02b8dcacd63e2ae8cddc5", "gitDir": "test/corpus/repos/javascript", - "sha2": "8d9d2fc7a193f89c45f0589e241af82762344f9d" + "sha2": "38b78fc259d249ae1a83a38b5a610b1ea4ffd17b" } ,{ "testCaseDescription": "javascript-nested-functions-delete-rest-test", @@ -340,7 +340,7 @@ "nested-functions.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -362,7 +362,7 @@ "filePaths": [ "nested-functions.js" ], - "sha1": "8d9d2fc7a193f89c45f0589e241af82762344f9d", + "sha1": "38b78fc259d249ae1a83a38b5a610b1ea4ffd17b", "gitDir": "test/corpus/repos/javascript", - "sha2": "f8683054b3df6a44185993d0c11c1edcf4477b16" + "sha2": "f330b79e26d2268d24e9ee9ba1fbb1c94d816e65" }] diff --git a/test/corpus/diff-summaries/javascript/null.json b/test/corpus/diff-summaries/javascript/null.json index f359c8c77..998ee744e 100644 --- a/test/corpus/diff-summaries/javascript/null.json +++ b/test/corpus/diff-summaries/javascript/null.json @@ -5,7 +5,7 @@ "null.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -27,9 +27,9 @@ "filePaths": [ "null.js" ], - "sha1": "5e6fd51739eb15db9fcd9e85e7f5c64da736056e", + "sha1": "704c62da36013859dd8e6a1139c4d908e22bc980", "gitDir": "test/corpus/repos/javascript", - "sha2": "09d001185168db0f5777db8bbe8fdbc2317850f3" + "sha2": "fb650c97f935c1a723fbfbaa541690a1a5d19c07" } ,{ "testCaseDescription": "javascript-null-replacement-insert-test", @@ -38,7 +38,7 @@ "null.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -55,7 +55,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 1 @@ -77,9 +77,9 @@ "filePaths": [ "null.js" ], - "sha1": "09d001185168db0f5777db8bbe8fdbc2317850f3", + "sha1": "fb650c97f935c1a723fbfbaa541690a1a5d19c07", "gitDir": "test/corpus/repos/javascript", - "sha2": "35e28a7dacfbe56dc784968b9a74dc237dc277a7" + "sha2": "2888848f2fc7ae75b57830fa7d44db6fb618e86f" } ,{ "testCaseDescription": "javascript-null-delete-insert-test", @@ -88,7 +88,7 @@ "null.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -105,7 +105,7 @@ }, { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -127,9 +127,9 @@ "filePaths": [ "null.js" ], - "sha1": "35e28a7dacfbe56dc784968b9a74dc237dc277a7", + "sha1": "2888848f2fc7ae75b57830fa7d44db6fb618e86f", "gitDir": "test/corpus/repos/javascript", - "sha2": "a8ddfdc834fb4cb46f918dd79169c0ba94039e28" + "sha2": "67b14c1f2c338f118cc8645a884945ad5b20be5c" } ,{ "testCaseDescription": "javascript-null-replacement-test", @@ -138,7 +138,7 @@ "null.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -155,7 +155,7 @@ }, { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -177,9 +177,9 @@ "filePaths": [ "null.js" ], - "sha1": "a8ddfdc834fb4cb46f918dd79169c0ba94039e28", + "sha1": "67b14c1f2c338f118cc8645a884945ad5b20be5c", "gitDir": "test/corpus/repos/javascript", - "sha2": "a7e58f47ba6bbf42e87feafd33a924b9cb7b81a6" + "sha2": "64a2fca3b0468d6445f67bc686e0155eb15a0e6e" } ,{ "testCaseDescription": "javascript-null-delete-replacement-test", @@ -188,7 +188,7 @@ "null.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -205,7 +205,7 @@ }, { "span": { - "this": { + "delete": { "start": [ 2, 1 @@ -222,7 +222,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 1 @@ -244,9 +244,9 @@ "filePaths": [ "null.js" ], - "sha1": "a7e58f47ba6bbf42e87feafd33a924b9cb7b81a6", + "sha1": "64a2fca3b0468d6445f67bc686e0155eb15a0e6e", "gitDir": "test/corpus/repos/javascript", - "sha2": "06a768142a69aa4d9537a4ff712fdd881d6dc58f" + "sha2": "ee2fcf5e976c4a8358149eb56112eaef153c13b2" } ,{ "testCaseDescription": "javascript-null-delete-test", @@ -255,7 +255,7 @@ "null.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -277,9 +277,9 @@ "filePaths": [ "null.js" ], - "sha1": "06a768142a69aa4d9537a4ff712fdd881d6dc58f", + "sha1": "ee2fcf5e976c4a8358149eb56112eaef153c13b2", "gitDir": "test/corpus/repos/javascript", - "sha2": "e5d2ffd3ec75871b9f3a6af9a32b67d9c38bc198" + "sha2": "2866dfd579a77d59617dc565a8bc2b0f412b1a5e" } ,{ "testCaseDescription": "javascript-null-delete-rest-test", @@ -288,7 +288,7 @@ "null.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -310,7 +310,7 @@ "filePaths": [ "null.js" ], - "sha1": "e5d2ffd3ec75871b9f3a6af9a32b67d9c38bc198", + "sha1": "2866dfd579a77d59617dc565a8bc2b0f412b1a5e", "gitDir": "test/corpus/repos/javascript", - "sha2": "0cf324666c04ffe5413f3e03ff09dc4a3883ab7c" + "sha2": "660e3a5b95669c843b77a62446f2e57dcde9e285" }] diff --git a/test/corpus/diff-summaries/javascript/number.json b/test/corpus/diff-summaries/javascript/number.json index 87e07ddad..56c91a562 100644 --- a/test/corpus/diff-summaries/javascript/number.json +++ b/test/corpus/diff-summaries/javascript/number.json @@ -5,7 +5,7 @@ "number.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -27,9 +27,9 @@ "filePaths": [ "number.js" ], - "sha1": "ca6f199fff7d76515b59c3e37344ea22225c3406", + "sha1": "ede522a00f4676035db2e9d76a9b702e5234917a", "gitDir": "test/corpus/repos/javascript", - "sha2": "d15dd98056d0af5e286aca858a31ef433e6f9218" + "sha2": "38114803fec2d221d3d6e204766200b7b04e0e27" } ,{ "testCaseDescription": "javascript-number-replacement-insert-test", @@ -38,7 +38,7 @@ "number.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -55,7 +55,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 1 @@ -77,9 +77,9 @@ "filePaths": [ "number.js" ], - "sha1": "d15dd98056d0af5e286aca858a31ef433e6f9218", + "sha1": "38114803fec2d221d3d6e204766200b7b04e0e27", "gitDir": "test/corpus/repos/javascript", - "sha2": "7f8fd62ebf444f3f84096aa3178029783c356279" + "sha2": "1545918b32f8c704efe91e7655442e328f98f43d" } ,{ "testCaseDescription": "javascript-number-delete-insert-test", @@ -88,7 +88,7 @@ "number.js": [ { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -123,9 +123,9 @@ "filePaths": [ "number.js" ], - "sha1": "7f8fd62ebf444f3f84096aa3178029783c356279", + "sha1": "1545918b32f8c704efe91e7655442e328f98f43d", "gitDir": "test/corpus/repos/javascript", - "sha2": "e057ec4e43f016f85bca7ecef40217f5b87cdb04" + "sha2": "c9fbddc95fbbb9a1acb697c5c072b8ffbe163336" } ,{ "testCaseDescription": "javascript-number-replacement-test", @@ -134,7 +134,7 @@ "number.js": [ { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -169,9 +169,9 @@ "filePaths": [ "number.js" ], - "sha1": "e057ec4e43f016f85bca7ecef40217f5b87cdb04", + "sha1": "c9fbddc95fbbb9a1acb697c5c072b8ffbe163336", "gitDir": "test/corpus/repos/javascript", - "sha2": "cccd069522c6d0d8d1b6b6313588d8a220089af9" + "sha2": "e27818b8f53204e17eb88985eaf49c9ea8ef4726" } ,{ "testCaseDescription": "javascript-number-delete-replacement-test", @@ -180,7 +180,7 @@ "number.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -197,7 +197,7 @@ }, { "span": { - "this": { + "delete": { "start": [ 2, 1 @@ -214,7 +214,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 1 @@ -236,9 +236,9 @@ "filePaths": [ "number.js" ], - "sha1": "cccd069522c6d0d8d1b6b6313588d8a220089af9", + "sha1": "e27818b8f53204e17eb88985eaf49c9ea8ef4726", "gitDir": "test/corpus/repos/javascript", - "sha2": "e35f20ba047877b52fa927f58d2e661e6d4b038d" + "sha2": "246413aa97cfb3cfec1874000969cd4374373f15" } ,{ "testCaseDescription": "javascript-number-delete-test", @@ -247,7 +247,7 @@ "number.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -269,9 +269,9 @@ "filePaths": [ "number.js" ], - "sha1": "e35f20ba047877b52fa927f58d2e661e6d4b038d", + "sha1": "246413aa97cfb3cfec1874000969cd4374373f15", "gitDir": "test/corpus/repos/javascript", - "sha2": "dd147ad548ac862d0191566bc6b706f0feb26a2c" + "sha2": "f0b25a1412833d0cdec38e7b8306ab6310704e72" } ,{ "testCaseDescription": "javascript-number-delete-rest-test", @@ -280,7 +280,7 @@ "number.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -302,7 +302,7 @@ "filePaths": [ "number.js" ], - "sha1": "dd147ad548ac862d0191566bc6b706f0feb26a2c", + "sha1": "f0b25a1412833d0cdec38e7b8306ab6310704e72", "gitDir": "test/corpus/repos/javascript", - "sha2": "45a6d97047c9425f56128ec4e4400027be11cad7" + "sha2": "6539b8361c59312164d8321ca3888c0511fcf849" }] diff --git a/test/corpus/diff-summaries/javascript/object-with-methods.json b/test/corpus/diff-summaries/javascript/object-with-methods.json index ec80c7d36..850e51b50 100644 --- a/test/corpus/diff-summaries/javascript/object-with-methods.json +++ b/test/corpus/diff-summaries/javascript/object-with-methods.json @@ -5,7 +5,7 @@ "objects-with-methods.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -27,9 +27,9 @@ "filePaths": [ "objects-with-methods.js" ], - "sha1": "96217c240d7773372a78d2a23601a4a97459fcad", + "sha1": "613f8b8ea74085ab35b7398fe3f636eda7d63fa2", "gitDir": "test/corpus/repos/javascript", - "sha2": "6e0b9bd4f9e342ac6f9ec1d77b3fc530ae87a9a2" + "sha2": "2e774e0d6c383c529d88e5606d8696e9ade47af3" } ,{ "testCaseDescription": "javascript-objects-with-methods-replacement-insert-test", @@ -38,7 +38,7 @@ "objects-with-methods.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -55,7 +55,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 1 @@ -77,9 +77,9 @@ "filePaths": [ "objects-with-methods.js" ], - "sha1": "6e0b9bd4f9e342ac6f9ec1d77b3fc530ae87a9a2", + "sha1": "2e774e0d6c383c529d88e5606d8696e9ade47af3", "gitDir": "test/corpus/repos/javascript", - "sha2": "20ddbd693493a945428ab017ad8562bebecc19eb" + "sha2": "9ac75c62eaf7cb66aff208ff41c1c39ea794d7e3" } ,{ "testCaseDescription": "javascript-objects-with-methods-delete-insert-test", @@ -88,7 +88,7 @@ "objects-with-methods.js": [ { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -123,9 +123,9 @@ "filePaths": [ "objects-with-methods.js" ], - "sha1": "20ddbd693493a945428ab017ad8562bebecc19eb", + "sha1": "9ac75c62eaf7cb66aff208ff41c1c39ea794d7e3", "gitDir": "test/corpus/repos/javascript", - "sha2": "e912fc9f4f009ec09d1c5cc288beea94f9b13de0" + "sha2": "f6d7a1f18d357f526c00dad5ab7e5f4094ff73a0" } ,{ "testCaseDescription": "javascript-objects-with-methods-replacement-test", @@ -134,7 +134,7 @@ "objects-with-methods.js": [ { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -169,9 +169,9 @@ "filePaths": [ "objects-with-methods.js" ], - "sha1": "e912fc9f4f009ec09d1c5cc288beea94f9b13de0", + "sha1": "f6d7a1f18d357f526c00dad5ab7e5f4094ff73a0", "gitDir": "test/corpus/repos/javascript", - "sha2": "62fdf99216ad8608e9371c76c05b1e4e5c5574d5" + "sha2": "02512232a51b3f33eace65e85b2ad927a200629d" } ,{ "testCaseDescription": "javascript-objects-with-methods-delete-replacement-test", @@ -180,7 +180,7 @@ "objects-with-methods.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -197,7 +197,7 @@ }, { "span": { - "this": { + "delete": { "start": [ 2, 1 @@ -214,7 +214,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 1 @@ -236,9 +236,9 @@ "filePaths": [ "objects-with-methods.js" ], - "sha1": "62fdf99216ad8608e9371c76c05b1e4e5c5574d5", + "sha1": "02512232a51b3f33eace65e85b2ad927a200629d", "gitDir": "test/corpus/repos/javascript", - "sha2": "48db8be531ea86fab4d79cddcc9378bbc0e26085" + "sha2": "52a1106dbdff953a566289445e06998e28f46f03" } ,{ "testCaseDescription": "javascript-objects-with-methods-delete-test", @@ -247,7 +247,7 @@ "objects-with-methods.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -269,9 +269,9 @@ "filePaths": [ "objects-with-methods.js" ], - "sha1": "48db8be531ea86fab4d79cddcc9378bbc0e26085", + "sha1": "52a1106dbdff953a566289445e06998e28f46f03", "gitDir": "test/corpus/repos/javascript", - "sha2": "67c7dde79edbfb3e52f0941c20215412fe63df35" + "sha2": "6b8bc1f10092271cab628b3e17f13524f28fdded" } ,{ "testCaseDescription": "javascript-objects-with-methods-delete-rest-test", @@ -280,7 +280,7 @@ "objects-with-methods.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -302,7 +302,7 @@ "filePaths": [ "objects-with-methods.js" ], - "sha1": "67c7dde79edbfb3e52f0941c20215412fe63df35", + "sha1": "6b8bc1f10092271cab628b3e17f13524f28fdded", "gitDir": "test/corpus/repos/javascript", - "sha2": "c889f65f6a973b3a266eb413d25af2589ac90aad" + "sha2": "f15ed2c50f158bdc680972378a52575dbc492025" }] diff --git a/test/corpus/diff-summaries/javascript/object.json b/test/corpus/diff-summaries/javascript/object.json index 66924c77e..703279d65 100644 --- a/test/corpus/diff-summaries/javascript/object.json +++ b/test/corpus/diff-summaries/javascript/object.json @@ -5,7 +5,7 @@ "object.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -27,9 +27,9 @@ "filePaths": [ "object.js" ], - "sha1": "25d0dca67cfd26a4d408ec7cc751b428dd7d0451", + "sha1": "f8683054b3df6a44185993d0c11c1edcf4477b16", "gitDir": "test/corpus/repos/javascript", - "sha2": "7f5cbbc47228c1104892eada850c44c6882f2e75" + "sha2": "06f986e188881d31280bf61fc28c2427ddeee3d6" } ,{ "testCaseDescription": "javascript-object-replacement-insert-test", @@ -38,7 +38,7 @@ "object.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -55,7 +55,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 1 @@ -77,9 +77,9 @@ "filePaths": [ "object.js" ], - "sha1": "7f5cbbc47228c1104892eada850c44c6882f2e75", + "sha1": "06f986e188881d31280bf61fc28c2427ddeee3d6", "gitDir": "test/corpus/repos/javascript", - "sha2": "af8e715d412674a9e461911257f6cf7300181ecf" + "sha2": "452ffb764876adf5738295d2aa3ec48ea9399761" } ,{ "testCaseDescription": "javascript-object-delete-insert-test", @@ -88,7 +88,7 @@ "object.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 21 @@ -105,7 +105,7 @@ }, { "span": { - "this": { + "delete": { "start": [ 1, 39 @@ -127,9 +127,9 @@ "filePaths": [ "object.js" ], - "sha1": "af8e715d412674a9e461911257f6cf7300181ecf", + "sha1": "452ffb764876adf5738295d2aa3ec48ea9399761", "gitDir": "test/corpus/repos/javascript", - "sha2": "de0bf64501649b87dfa7c4cb899f7d3b10e0aeb2" + "sha2": "2e57b5ec821611bfbf24b3d9d73e0ea8bee50624" } ,{ "testCaseDescription": "javascript-object-replacement-test", @@ -138,7 +138,7 @@ "object.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 21 @@ -155,7 +155,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 1, 39 @@ -177,9 +177,9 @@ "filePaths": [ "object.js" ], - "sha1": "de0bf64501649b87dfa7c4cb899f7d3b10e0aeb2", + "sha1": "2e57b5ec821611bfbf24b3d9d73e0ea8bee50624", "gitDir": "test/corpus/repos/javascript", - "sha2": "1edcda3336c0e559ed414893984424a0a3933d46" + "sha2": "b7905f5c7b310ff395bb7882055844a18b45baf2" } ,{ "testCaseDescription": "javascript-object-delete-replacement-test", @@ -188,7 +188,7 @@ "object.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -205,7 +205,7 @@ }, { "span": { - "this": { + "delete": { "start": [ 2, 1 @@ -222,7 +222,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 1 @@ -244,9 +244,9 @@ "filePaths": [ "object.js" ], - "sha1": "1edcda3336c0e559ed414893984424a0a3933d46", + "sha1": "b7905f5c7b310ff395bb7882055844a18b45baf2", "gitDir": "test/corpus/repos/javascript", - "sha2": "876287a27a2dd4a49bc577d774257cea7c86f22d" + "sha2": "52c7c26f74741c4f26effb3b6efe111830bb0e0c" } ,{ "testCaseDescription": "javascript-object-delete-test", @@ -255,7 +255,7 @@ "object.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -277,9 +277,9 @@ "filePaths": [ "object.js" ], - "sha1": "876287a27a2dd4a49bc577d774257cea7c86f22d", + "sha1": "52c7c26f74741c4f26effb3b6efe111830bb0e0c", "gitDir": "test/corpus/repos/javascript", - "sha2": "0186f0d7bd20043d83475e7c5f601ab06c156246" + "sha2": "9ffa4ea63cd2c434126197fb165c67412a4c8130" } ,{ "testCaseDescription": "javascript-object-delete-rest-test", @@ -288,7 +288,7 @@ "object.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -310,7 +310,7 @@ "filePaths": [ "object.js" ], - "sha1": "0186f0d7bd20043d83475e7c5f601ab06c156246", + "sha1": "9ffa4ea63cd2c434126197fb165c67412a4c8130", "gitDir": "test/corpus/repos/javascript", - "sha2": "2f014a3eddb509376944a4938ace7c0eb952308d" + "sha2": "b4b200a6398403b141e5fd87506899af661b97a6" }] diff --git a/test/corpus/diff-summaries/javascript/regex.json b/test/corpus/diff-summaries/javascript/regex.json index 6f486f11c..a1e2a55da 100644 --- a/test/corpus/diff-summaries/javascript/regex.json +++ b/test/corpus/diff-summaries/javascript/regex.json @@ -5,7 +5,7 @@ "regex.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -27,9 +27,9 @@ "filePaths": [ "regex.js" ], - "sha1": "a23b0a588d860380edd5b815810c34e35d5855a8", + "sha1": "1980a80ff9a2f2886b85d2e8ce9df29b1f7adad5", "gitDir": "test/corpus/repos/javascript", - "sha2": "217e36b213c91a65d77f46926fcb534902df7e19" + "sha2": "6a3727ab152c2ce63c9771e6c86f1ce2659a85e2" } ,{ "testCaseDescription": "javascript-regex-replacement-insert-test", @@ -38,7 +38,7 @@ "regex.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -55,7 +55,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 1 @@ -77,9 +77,9 @@ "filePaths": [ "regex.js" ], - "sha1": "217e36b213c91a65d77f46926fcb534902df7e19", + "sha1": "6a3727ab152c2ce63c9771e6c86f1ce2659a85e2", "gitDir": "test/corpus/repos/javascript", - "sha2": "4a52d9e2ec880aa7188150f006b90c8917423bd4" + "sha2": "330b5f33c8c67a52d33d007192b6e5e2eca2b6eb" } ,{ "testCaseDescription": "javascript-regex-delete-insert-test", @@ -88,7 +88,7 @@ "regex.js": [ { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -123,9 +123,9 @@ "filePaths": [ "regex.js" ], - "sha1": "4a52d9e2ec880aa7188150f006b90c8917423bd4", + "sha1": "330b5f33c8c67a52d33d007192b6e5e2eca2b6eb", "gitDir": "test/corpus/repos/javascript", - "sha2": "f59bede5c9d87962f3ccd92e92b8033b62df42d6" + "sha2": "0df0ff208ecda7e3fe1ec07720ca4e2d5ca97abe" } ,{ "testCaseDescription": "javascript-regex-replacement-test", @@ -134,7 +134,7 @@ "regex.js": [ { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -169,9 +169,9 @@ "filePaths": [ "regex.js" ], - "sha1": "f59bede5c9d87962f3ccd92e92b8033b62df42d6", + "sha1": "0df0ff208ecda7e3fe1ec07720ca4e2d5ca97abe", "gitDir": "test/corpus/repos/javascript", - "sha2": "fd2e9c9a9fc22df2f9d419ca900cd31829009900" + "sha2": "815037f8db1286618f7fe00d93247c8abeec2e8b" } ,{ "testCaseDescription": "javascript-regex-delete-replacement-test", @@ -180,7 +180,7 @@ "regex.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -197,7 +197,7 @@ }, { "span": { - "this": { + "delete": { "start": [ 2, 1 @@ -214,7 +214,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 1 @@ -236,9 +236,9 @@ "filePaths": [ "regex.js" ], - "sha1": "fd2e9c9a9fc22df2f9d419ca900cd31829009900", + "sha1": "815037f8db1286618f7fe00d93247c8abeec2e8b", "gitDir": "test/corpus/repos/javascript", - "sha2": "f1bb99be7d4da0912f1a327169283becd330cee2" + "sha2": "085e1d0671ddbeb65df8785014418f4dd5e406fb" } ,{ "testCaseDescription": "javascript-regex-delete-test", @@ -247,7 +247,7 @@ "regex.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -269,9 +269,9 @@ "filePaths": [ "regex.js" ], - "sha1": "f1bb99be7d4da0912f1a327169283becd330cee2", + "sha1": "085e1d0671ddbeb65df8785014418f4dd5e406fb", "gitDir": "test/corpus/repos/javascript", - "sha2": "7f501f49c0f89042f4f95f6a52e1a984fe76176a" + "sha2": "2320ce8ffa14273ff3094b25c293920a117cdfb5" } ,{ "testCaseDescription": "javascript-regex-delete-rest-test", @@ -280,7 +280,7 @@ "regex.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -302,7 +302,7 @@ "filePaths": [ "regex.js" ], - "sha1": "7f501f49c0f89042f4f95f6a52e1a984fe76176a", + "sha1": "2320ce8ffa14273ff3094b25c293920a117cdfb5", "gitDir": "test/corpus/repos/javascript", - "sha2": "f4a276fc53b44233f1996fab1c4310602ddc195f" + "sha2": "b8ad05d0253ae191a5f160e7048edd003cbfd266" }] diff --git a/test/corpus/diff-summaries/javascript/relational-operator.json b/test/corpus/diff-summaries/javascript/relational-operator.json index 9795d09af..8d307fe06 100644 --- a/test/corpus/diff-summaries/javascript/relational-operator.json +++ b/test/corpus/diff-summaries/javascript/relational-operator.json @@ -5,7 +5,7 @@ "relational-operator.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -27,9 +27,9 @@ "filePaths": [ "relational-operator.js" ], - "sha1": "0d4682971dbf0345afd2593f1068dc25c4cd0e84", + "sha1": "44726d92bc92a8541b8e3089ee22826fa31cdc69", "gitDir": "test/corpus/repos/javascript", - "sha2": "effcf61b37fbba12b7e8b2c9c987cf33c2814eb5" + "sha2": "a33204dd9472bf38dca8550758c5c87b533204e5" } ,{ "testCaseDescription": "javascript-relational-operator-replacement-insert-test", @@ -38,7 +38,7 @@ "relational-operator.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -55,7 +55,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 1 @@ -77,9 +77,9 @@ "filePaths": [ "relational-operator.js" ], - "sha1": "effcf61b37fbba12b7e8b2c9c987cf33c2814eb5", + "sha1": "a33204dd9472bf38dca8550758c5c87b533204e5", "gitDir": "test/corpus/repos/javascript", - "sha2": "689679d7cbce619b3cebc7a5492e6ccbe1cb7f5a" + "sha2": "2b464738a19e0a18863b2a4f8a656e9416dcfffc" } ,{ "testCaseDescription": "javascript-relational-operator-delete-insert-test", @@ -90,9 +90,9 @@ "filePaths": [ "relational-operator.js" ], - "sha1": "689679d7cbce619b3cebc7a5492e6ccbe1cb7f5a", + "sha1": "2b464738a19e0a18863b2a4f8a656e9416dcfffc", "gitDir": "test/corpus/repos/javascript", - "sha2": "88f87130aa4119c6be38c89cfa33f76a31ed1924" + "sha2": "48ed1f73ff525a6ec7c6cda70d4f9587102dab7d" } ,{ "testCaseDescription": "javascript-relational-operator-replacement-test", @@ -103,9 +103,9 @@ "filePaths": [ "relational-operator.js" ], - "sha1": "88f87130aa4119c6be38c89cfa33f76a31ed1924", + "sha1": "48ed1f73ff525a6ec7c6cda70d4f9587102dab7d", "gitDir": "test/corpus/repos/javascript", - "sha2": "0e932c3e06f7ab7e22bccd7b27d0dd90a459709e" + "sha2": "db672c2dad46487be60f96146b29937c001ba2b1" } ,{ "testCaseDescription": "javascript-relational-operator-delete-replacement-test", @@ -114,7 +114,7 @@ "relational-operator.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -136,9 +136,9 @@ "filePaths": [ "relational-operator.js" ], - "sha1": "0e932c3e06f7ab7e22bccd7b27d0dd90a459709e", + "sha1": "db672c2dad46487be60f96146b29937c001ba2b1", "gitDir": "test/corpus/repos/javascript", - "sha2": "0c735369dcf138f48d54d653d9d6f6b54c6152a4" + "sha2": "bd6cf287a138becb71cae777b80c5395be91d0d6" } ,{ "testCaseDescription": "javascript-relational-operator-delete-test", @@ -147,7 +147,7 @@ "relational-operator.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -169,9 +169,9 @@ "filePaths": [ "relational-operator.js" ], - "sha1": "0c735369dcf138f48d54d653d9d6f6b54c6152a4", + "sha1": "bd6cf287a138becb71cae777b80c5395be91d0d6", "gitDir": "test/corpus/repos/javascript", - "sha2": "1f0c2c97efb56381e072d3abba5bb3d1739d39f1" + "sha2": "aa476186f44557e5ab77592974a40ff32534eab7" } ,{ "testCaseDescription": "javascript-relational-operator-delete-rest-test", @@ -180,7 +180,7 @@ "relational-operator.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -202,7 +202,7 @@ "filePaths": [ "relational-operator.js" ], - "sha1": "1f0c2c97efb56381e072d3abba5bb3d1739d39f1", + "sha1": "aa476186f44557e5ab77592974a40ff32534eab7", "gitDir": "test/corpus/repos/javascript", - "sha2": "b7399e257e9ce0b28ce3080ac7e8edb2778614a3" + "sha2": "af26873a60eeb28bb292941d2ee8cae7449c9a37" }] diff --git a/test/corpus/diff-summaries/javascript/return-statement.json b/test/corpus/diff-summaries/javascript/return-statement.json index 2b28975ec..f4078fb53 100644 --- a/test/corpus/diff-summaries/javascript/return-statement.json +++ b/test/corpus/diff-summaries/javascript/return-statement.json @@ -5,7 +5,7 @@ "return-statement.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -27,9 +27,9 @@ "filePaths": [ "return-statement.js" ], - "sha1": "ea1cb608a188b06972bcdf47db341f8b953076b1", + "sha1": "c2a48d97ae6754bf21e1dbfa2e13bde3f68deb9c", "gitDir": "test/corpus/repos/javascript", - "sha2": "d6d43126c146818136ee53240cc0710fa5d6d5dd" + "sha2": "f16f5a51f1d033e808ef534924e1d91c77775b2e" } ,{ "testCaseDescription": "javascript-return-statement-replacement-insert-test", @@ -38,7 +38,7 @@ "return-statement.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -55,7 +55,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 1 @@ -77,9 +77,9 @@ "filePaths": [ "return-statement.js" ], - "sha1": "d6d43126c146818136ee53240cc0710fa5d6d5dd", + "sha1": "f16f5a51f1d033e808ef534924e1d91c77775b2e", "gitDir": "test/corpus/repos/javascript", - "sha2": "66af3d2ede52997e1459b9982344eea628c78ec1" + "sha2": "bdacda3ebb5cc26919466bb73dfdd7bc1f50861e" } ,{ "testCaseDescription": "javascript-return-statement-delete-insert-test", @@ -88,7 +88,7 @@ "return-statement.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 8 @@ -110,9 +110,9 @@ "filePaths": [ "return-statement.js" ], - "sha1": "66af3d2ede52997e1459b9982344eea628c78ec1", + "sha1": "bdacda3ebb5cc26919466bb73dfdd7bc1f50861e", "gitDir": "test/corpus/repos/javascript", - "sha2": "d69b3b6c2cf5dbbfe05929c9ccd38f9e70db044f" + "sha2": "515deebc3a3b05742d2019379e43d547b4d2f3e7" } ,{ "testCaseDescription": "javascript-return-statement-replacement-test", @@ -121,7 +121,7 @@ "return-statement.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 8 @@ -143,9 +143,9 @@ "filePaths": [ "return-statement.js" ], - "sha1": "d69b3b6c2cf5dbbfe05929c9ccd38f9e70db044f", + "sha1": "515deebc3a3b05742d2019379e43d547b4d2f3e7", "gitDir": "test/corpus/repos/javascript", - "sha2": "dc2e62f6d42b3b407e2f467005d0013c4d49d506" + "sha2": "ea03eba44176d1262daab2a8359dea97487df79c" } ,{ "testCaseDescription": "javascript-return-statement-delete-replacement-test", @@ -154,7 +154,7 @@ "return-statement.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -171,7 +171,7 @@ }, { "span": { - "this": { + "delete": { "start": [ 2, 1 @@ -188,7 +188,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 1 @@ -210,9 +210,9 @@ "filePaths": [ "return-statement.js" ], - "sha1": "dc2e62f6d42b3b407e2f467005d0013c4d49d506", + "sha1": "ea03eba44176d1262daab2a8359dea97487df79c", "gitDir": "test/corpus/repos/javascript", - "sha2": "0399b8e3ad0efd3c8c08b55e737025295e717c68" + "sha2": "f0d57f8e4dc9624fb4d9916a06b52aa20f597a1f" } ,{ "testCaseDescription": "javascript-return-statement-delete-test", @@ -221,7 +221,7 @@ "return-statement.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -243,9 +243,9 @@ "filePaths": [ "return-statement.js" ], - "sha1": "0399b8e3ad0efd3c8c08b55e737025295e717c68", + "sha1": "f0d57f8e4dc9624fb4d9916a06b52aa20f597a1f", "gitDir": "test/corpus/repos/javascript", - "sha2": "46019b62030cdac776e7844c5e07901b0d2934d3" + "sha2": "664d2f39a09675e0e17a3e1f595654fbe608b67d" } ,{ "testCaseDescription": "javascript-return-statement-delete-rest-test", @@ -254,7 +254,7 @@ "return-statement.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -276,7 +276,7 @@ "filePaths": [ "return-statement.js" ], - "sha1": "46019b62030cdac776e7844c5e07901b0d2934d3", + "sha1": "664d2f39a09675e0e17a3e1f595654fbe608b67d", "gitDir": "test/corpus/repos/javascript", - "sha2": "b9adfaa1ed76ab8073a888953b9f52ed07ae901d" + "sha2": "07e2e44f7f0b200f4b3454b91a777075ca8a6bf6" }] diff --git a/test/corpus/diff-summaries/javascript/string.json b/test/corpus/diff-summaries/javascript/string.json index 6438e4bee..7174e0e14 100644 --- a/test/corpus/diff-summaries/javascript/string.json +++ b/test/corpus/diff-summaries/javascript/string.json @@ -5,7 +5,7 @@ "string.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -27,9 +27,9 @@ "filePaths": [ "string.js" ], - "sha1": "c889f65f6a973b3a266eb413d25af2589ac90aad", + "sha1": "f15ed2c50f158bdc680972378a52575dbc492025", "gitDir": "test/corpus/repos/javascript", - "sha2": "821617bc632d99ebd1f9fd30b237096231b0e15d" + "sha2": "9b9896d1260c7f4b9fd7388f1f4b403f6a597d93" } ,{ "testCaseDescription": "javascript-string-replacement-insert-test", @@ -38,7 +38,7 @@ "string.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -55,7 +55,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 1 @@ -77,9 +77,9 @@ "filePaths": [ "string.js" ], - "sha1": "821617bc632d99ebd1f9fd30b237096231b0e15d", + "sha1": "9b9896d1260c7f4b9fd7388f1f4b403f6a597d93", "gitDir": "test/corpus/repos/javascript", - "sha2": "1e2dcdc8a9a18a7d337d93009fbe9658db462783" + "sha2": "cbcb811994dcd0272b76076688ef0a610d9a4ca5" } ,{ "testCaseDescription": "javascript-string-delete-insert-test", @@ -88,7 +88,7 @@ "string.js": [ { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -123,9 +123,9 @@ "filePaths": [ "string.js" ], - "sha1": "1e2dcdc8a9a18a7d337d93009fbe9658db462783", + "sha1": "cbcb811994dcd0272b76076688ef0a610d9a4ca5", "gitDir": "test/corpus/repos/javascript", - "sha2": "b3db1e245fd2d0ad01e0e27460d6e97af1c564db" + "sha2": "d86a5265e2bccf5373edf45ce3cf23c44f0cd605" } ,{ "testCaseDescription": "javascript-string-replacement-test", @@ -134,7 +134,7 @@ "string.js": [ { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -169,9 +169,9 @@ "filePaths": [ "string.js" ], - "sha1": "b3db1e245fd2d0ad01e0e27460d6e97af1c564db", + "sha1": "d86a5265e2bccf5373edf45ce3cf23c44f0cd605", "gitDir": "test/corpus/repos/javascript", - "sha2": "ca7fee05b34e388c9734c71b906655bcf6f01295" + "sha2": "c8b7ef7072fa07bd00b6784fbde52b446fb338e9" } ,{ "testCaseDescription": "javascript-string-delete-replacement-test", @@ -180,7 +180,7 @@ "string.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -197,7 +197,7 @@ }, { "span": { - "this": { + "delete": { "start": [ 2, 1 @@ -214,7 +214,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 1 @@ -236,9 +236,9 @@ "filePaths": [ "string.js" ], - "sha1": "ca7fee05b34e388c9734c71b906655bcf6f01295", + "sha1": "c8b7ef7072fa07bd00b6784fbde52b446fb338e9", "gitDir": "test/corpus/repos/javascript", - "sha2": "293106e45dc93d792c0e410c81728e60e60dc090" + "sha2": "298da348c90a750fb5171af2a58d8813eb064f8f" } ,{ "testCaseDescription": "javascript-string-delete-test", @@ -247,7 +247,7 @@ "string.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -269,9 +269,9 @@ "filePaths": [ "string.js" ], - "sha1": "293106e45dc93d792c0e410c81728e60e60dc090", + "sha1": "298da348c90a750fb5171af2a58d8813eb064f8f", "gitDir": "test/corpus/repos/javascript", - "sha2": "4a11d9c2213843857f1f4eddf9c3980aaabcdeaa" + "sha2": "8c867f1717adf94286335d942f2a343c759e2d07" } ,{ "testCaseDescription": "javascript-string-delete-rest-test", @@ -280,7 +280,7 @@ "string.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -302,7 +302,7 @@ "filePaths": [ "string.js" ], - "sha1": "4a11d9c2213843857f1f4eddf9c3980aaabcdeaa", + "sha1": "8c867f1717adf94286335d942f2a343c759e2d07", "gitDir": "test/corpus/repos/javascript", - "sha2": "ca6f199fff7d76515b59c3e37344ea22225c3406" + "sha2": "ede522a00f4676035db2e9d76a9b702e5234917a" }] diff --git a/test/corpus/diff-summaries/javascript/subscript-access-assignment.json b/test/corpus/diff-summaries/javascript/subscript-access-assignment.json index 395bc60f7..36d2f2b76 100644 --- a/test/corpus/diff-summaries/javascript/subscript-access-assignment.json +++ b/test/corpus/diff-summaries/javascript/subscript-access-assignment.json @@ -5,7 +5,7 @@ "subscript-access-assignment.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -27,9 +27,9 @@ "filePaths": [ "subscript-access-assignment.js" ], - "sha1": "2777fc53b2f1b0e54aead0a015db9970af0795fe", + "sha1": "e7314eba8beae9be9a34bcf91157e5e542f4b2a9", "gitDir": "test/corpus/repos/javascript", - "sha2": "56d078c8be955e974b02bb9413e8196e0e092cdb" + "sha2": "2dcf6f61922c7877db63fc6e1160809305c734fc" } ,{ "testCaseDescription": "javascript-subscript-access-assignment-replacement-insert-test", @@ -38,7 +38,7 @@ "subscript-access-assignment.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -55,7 +55,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 1 @@ -77,9 +77,9 @@ "filePaths": [ "subscript-access-assignment.js" ], - "sha1": "56d078c8be955e974b02bb9413e8196e0e092cdb", + "sha1": "2dcf6f61922c7877db63fc6e1160809305c734fc", "gitDir": "test/corpus/repos/javascript", - "sha2": "b6764107f971cb9f7ddf592f63c48d6e7920eb79" + "sha2": "da6d1a9623b7a97faec75d5384358f7f8593f799" } ,{ "testCaseDescription": "javascript-subscript-access-assignment-delete-insert-test", @@ -88,7 +88,7 @@ "subscript-access-assignment.js": [ { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -123,9 +123,9 @@ "filePaths": [ "subscript-access-assignment.js" ], - "sha1": "b6764107f971cb9f7ddf592f63c48d6e7920eb79", + "sha1": "da6d1a9623b7a97faec75d5384358f7f8593f799", "gitDir": "test/corpus/repos/javascript", - "sha2": "c6cf46d469bff2839ea43d397a672cfeefb7fed3" + "sha2": "8b811c2aa46341ef0e9edcf76b101e169478425f" } ,{ "testCaseDescription": "javascript-subscript-access-assignment-replacement-test", @@ -134,7 +134,7 @@ "subscript-access-assignment.js": [ { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -169,9 +169,9 @@ "filePaths": [ "subscript-access-assignment.js" ], - "sha1": "c6cf46d469bff2839ea43d397a672cfeefb7fed3", + "sha1": "8b811c2aa46341ef0e9edcf76b101e169478425f", "gitDir": "test/corpus/repos/javascript", - "sha2": "be2f114b3b50c34e16eb2a9201b3b63ba6a08617" + "sha2": "cd0920678a4dda65b9457809726f0f1fcd82fe32" } ,{ "testCaseDescription": "javascript-subscript-access-assignment-delete-replacement-test", @@ -180,7 +180,7 @@ "subscript-access-assignment.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -197,7 +197,7 @@ }, { "span": { - "this": { + "delete": { "start": [ 2, 1 @@ -214,7 +214,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 1 @@ -236,9 +236,9 @@ "filePaths": [ "subscript-access-assignment.js" ], - "sha1": "be2f114b3b50c34e16eb2a9201b3b63ba6a08617", + "sha1": "cd0920678a4dda65b9457809726f0f1fcd82fe32", "gitDir": "test/corpus/repos/javascript", - "sha2": "5ca3653b76f677ce067dc9c1509ab906f205cd1b" + "sha2": "5eec10c41bb97d646fb56a6bc004589909467a6e" } ,{ "testCaseDescription": "javascript-subscript-access-assignment-delete-test", @@ -247,7 +247,7 @@ "subscript-access-assignment.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -269,9 +269,9 @@ "filePaths": [ "subscript-access-assignment.js" ], - "sha1": "5ca3653b76f677ce067dc9c1509ab906f205cd1b", + "sha1": "5eec10c41bb97d646fb56a6bc004589909467a6e", "gitDir": "test/corpus/repos/javascript", - "sha2": "5e1b3305c8e5ffeaffd2e5a040a07fe6e1965484" + "sha2": "4b19e000c5b0de14105304c9d033151a30907c57" } ,{ "testCaseDescription": "javascript-subscript-access-assignment-delete-rest-test", @@ -280,7 +280,7 @@ "subscript-access-assignment.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -302,7 +302,7 @@ "filePaths": [ "subscript-access-assignment.js" ], - "sha1": "5e1b3305c8e5ffeaffd2e5a040a07fe6e1965484", + "sha1": "4b19e000c5b0de14105304c9d033151a30907c57", "gitDir": "test/corpus/repos/javascript", - "sha2": "1cda03e29bc707037e0b55c899bc9d9fec1239db" + "sha2": "439dff969c87787fe222d1721433c8fafb0f1a89" }] diff --git a/test/corpus/diff-summaries/javascript/subscript-access-string.json b/test/corpus/diff-summaries/javascript/subscript-access-string.json index 5d181b82c..39d90e355 100644 --- a/test/corpus/diff-summaries/javascript/subscript-access-string.json +++ b/test/corpus/diff-summaries/javascript/subscript-access-string.json @@ -5,7 +5,7 @@ "subscript-access-string.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -27,9 +27,9 @@ "filePaths": [ "subscript-access-string.js" ], - "sha1": "7ae7a3452b9ea0561d469df9ecaf32e6eb2d9474", + "sha1": "3df0f065d7b873dd4eba9b0ca3ab7ec5820f3906", "gitDir": "test/corpus/repos/javascript", - "sha2": "5ff8e2661eac926dd7ed244797f9eada19ad7f5d" + "sha2": "108b26851b71b6768ab94313c970479637d5a048" } ,{ "testCaseDescription": "javascript-subscript-access-string-replacement-insert-test", @@ -38,7 +38,7 @@ "subscript-access-string.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -55,7 +55,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 1 @@ -77,9 +77,9 @@ "filePaths": [ "subscript-access-string.js" ], - "sha1": "5ff8e2661eac926dd7ed244797f9eada19ad7f5d", + "sha1": "108b26851b71b6768ab94313c970479637d5a048", "gitDir": "test/corpus/repos/javascript", - "sha2": "9af8071731157d775318d5114e4dcac580f6f716" + "sha2": "b4cf95e3d18f381f29116f92faa6c956c93798eb" } ,{ "testCaseDescription": "javascript-subscript-access-string-delete-insert-test", @@ -88,7 +88,7 @@ "subscript-access-string.js": [ { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -123,9 +123,9 @@ "filePaths": [ "subscript-access-string.js" ], - "sha1": "9af8071731157d775318d5114e4dcac580f6f716", + "sha1": "b4cf95e3d18f381f29116f92faa6c956c93798eb", "gitDir": "test/corpus/repos/javascript", - "sha2": "eae6318d1c52e7127cc46aff2e75528ad361f57c" + "sha2": "a6ee628c26779ca0148017f0f302db74d74756ca" } ,{ "testCaseDescription": "javascript-subscript-access-string-replacement-test", @@ -134,7 +134,7 @@ "subscript-access-string.js": [ { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -169,9 +169,9 @@ "filePaths": [ "subscript-access-string.js" ], - "sha1": "eae6318d1c52e7127cc46aff2e75528ad361f57c", + "sha1": "a6ee628c26779ca0148017f0f302db74d74756ca", "gitDir": "test/corpus/repos/javascript", - "sha2": "58eaf98e9194b3d599455e7e5f250a420f82d155" + "sha2": "007983b635c9d206aaf43d9057ae073c5e26fc6d" } ,{ "testCaseDescription": "javascript-subscript-access-string-delete-replacement-test", @@ -180,7 +180,7 @@ "subscript-access-string.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -197,7 +197,7 @@ }, { "span": { - "this": { + "delete": { "start": [ 2, 1 @@ -214,7 +214,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 1 @@ -236,9 +236,9 @@ "filePaths": [ "subscript-access-string.js" ], - "sha1": "58eaf98e9194b3d599455e7e5f250a420f82d155", + "sha1": "007983b635c9d206aaf43d9057ae073c5e26fc6d", "gitDir": "test/corpus/repos/javascript", - "sha2": "8474b084fdbea46f9d61c8f84a08a1b65312a389" + "sha2": "ab8fffe8032e5c03df3a9f15e4e7c4531efef0ec" } ,{ "testCaseDescription": "javascript-subscript-access-string-delete-test", @@ -247,7 +247,7 @@ "subscript-access-string.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -269,9 +269,9 @@ "filePaths": [ "subscript-access-string.js" ], - "sha1": "8474b084fdbea46f9d61c8f84a08a1b65312a389", + "sha1": "ab8fffe8032e5c03df3a9f15e4e7c4531efef0ec", "gitDir": "test/corpus/repos/javascript", - "sha2": "72743b4417df690550bad30298e5a3fcf7b72115" + "sha2": "d2ad24f037597d94d511fd2264fd26d453969c27" } ,{ "testCaseDescription": "javascript-subscript-access-string-delete-rest-test", @@ -280,7 +280,7 @@ "subscript-access-string.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -302,7 +302,7 @@ "filePaths": [ "subscript-access-string.js" ], - "sha1": "72743b4417df690550bad30298e5a3fcf7b72115", + "sha1": "d2ad24f037597d94d511fd2264fd26d453969c27", "gitDir": "test/corpus/repos/javascript", - "sha2": "6d2a9f7093c2227f7d7eeedabf694118f5f17c73" + "sha2": "41bf287dfe63a1096787b4f7409a469d078c25b7" }] diff --git a/test/corpus/diff-summaries/javascript/subscript-access-variable.json b/test/corpus/diff-summaries/javascript/subscript-access-variable.json index 460b875c6..ed1d3f0d2 100644 --- a/test/corpus/diff-summaries/javascript/subscript-access-variable.json +++ b/test/corpus/diff-summaries/javascript/subscript-access-variable.json @@ -5,7 +5,7 @@ "subscript-access-variable.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -27,9 +27,9 @@ "filePaths": [ "subscript-access-variable.js" ], - "sha1": "0c9b3b84cb49951e79891dae24edfddccbf579a1", + "sha1": "6d6d0fda6116e0504607e3b9d770f51596723212", "gitDir": "test/corpus/repos/javascript", - "sha2": "f439893abc29fa3d1b29d471dd98f96e90ee2697" + "sha2": "e9f0a782313a5481e7aacda482f9a7db8bbb71ab" } ,{ "testCaseDescription": "javascript-subscript-access-variable-replacement-insert-test", @@ -38,7 +38,7 @@ "subscript-access-variable.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -55,7 +55,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 1 @@ -77,9 +77,9 @@ "filePaths": [ "subscript-access-variable.js" ], - "sha1": "f439893abc29fa3d1b29d471dd98f96e90ee2697", + "sha1": "e9f0a782313a5481e7aacda482f9a7db8bbb71ab", "gitDir": "test/corpus/repos/javascript", - "sha2": "20336b12a08bcd4c21d5dc3924b33c890e7756f5" + "sha2": "b8ee9f93050067378e2b6da9e2babaecb45915f4" } ,{ "testCaseDescription": "javascript-subscript-access-variable-delete-insert-test", @@ -88,7 +88,7 @@ "subscript-access-variable.js": [ { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -123,9 +123,9 @@ "filePaths": [ "subscript-access-variable.js" ], - "sha1": "20336b12a08bcd4c21d5dc3924b33c890e7756f5", + "sha1": "b8ee9f93050067378e2b6da9e2babaecb45915f4", "gitDir": "test/corpus/repos/javascript", - "sha2": "4a075f832e204bbf26ded5314cfb891513b549d6" + "sha2": "1b79e00006cb344b231833c29178306caf8374f6" } ,{ "testCaseDescription": "javascript-subscript-access-variable-replacement-test", @@ -134,7 +134,7 @@ "subscript-access-variable.js": [ { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -169,9 +169,9 @@ "filePaths": [ "subscript-access-variable.js" ], - "sha1": "4a075f832e204bbf26ded5314cfb891513b549d6", + "sha1": "1b79e00006cb344b231833c29178306caf8374f6", "gitDir": "test/corpus/repos/javascript", - "sha2": "d23a59eb43de72ee6594bb44bc987fc0b650c965" + "sha2": "1212ba90e58487b5994b8b685786461fe55bc66b" } ,{ "testCaseDescription": "javascript-subscript-access-variable-delete-replacement-test", @@ -180,7 +180,7 @@ "subscript-access-variable.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -197,7 +197,7 @@ }, { "span": { - "this": { + "delete": { "start": [ 2, 1 @@ -214,7 +214,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 1 @@ -236,9 +236,9 @@ "filePaths": [ "subscript-access-variable.js" ], - "sha1": "d23a59eb43de72ee6594bb44bc987fc0b650c965", + "sha1": "1212ba90e58487b5994b8b685786461fe55bc66b", "gitDir": "test/corpus/repos/javascript", - "sha2": "255b019fc84f0488a1de3ed0b4f3c3ad28aa365a" + "sha2": "48061d0539866aebd56ffa52b4210ac55cb87ad9" } ,{ "testCaseDescription": "javascript-subscript-access-variable-delete-test", @@ -247,7 +247,7 @@ "subscript-access-variable.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -269,9 +269,9 @@ "filePaths": [ "subscript-access-variable.js" ], - "sha1": "255b019fc84f0488a1de3ed0b4f3c3ad28aa365a", + "sha1": "48061d0539866aebd56ffa52b4210ac55cb87ad9", "gitDir": "test/corpus/repos/javascript", - "sha2": "df97f6eeaaa076e805e66e1bcf98403493d92c2f" + "sha2": "b271584c1989c4968ad62cdeec000ed54714db57" } ,{ "testCaseDescription": "javascript-subscript-access-variable-delete-rest-test", @@ -280,7 +280,7 @@ "subscript-access-variable.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -302,7 +302,7 @@ "filePaths": [ "subscript-access-variable.js" ], - "sha1": "df97f6eeaaa076e805e66e1bcf98403493d92c2f", + "sha1": "b271584c1989c4968ad62cdeec000ed54714db57", "gitDir": "test/corpus/repos/javascript", - "sha2": "7ae7a3452b9ea0561d469df9ecaf32e6eb2d9474" + "sha2": "3df0f065d7b873dd4eba9b0ca3ab7ec5820f3906" }] diff --git a/test/corpus/diff-summaries/javascript/switch-statement.json b/test/corpus/diff-summaries/javascript/switch-statement.json index fc7e5f6d0..0c6781cd7 100644 --- a/test/corpus/diff-summaries/javascript/switch-statement.json +++ b/test/corpus/diff-summaries/javascript/switch-statement.json @@ -5,7 +5,7 @@ "switch-statement.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -27,9 +27,9 @@ "filePaths": [ "switch-statement.js" ], - "sha1": "ebc2ca02f6b0c4744e33e2d191158cc7f2b19a60", + "sha1": "011a5d6edc417ef0abbfb325ad08abdb917f4184", "gitDir": "test/corpus/repos/javascript", - "sha2": "cbc2b0ea47a2cd6fb09368f3c72e101f946c4b26" + "sha2": "f5f92d14854e8f589966634672d4609022ac912d" } ,{ "testCaseDescription": "javascript-switch-statement-replacement-insert-test", @@ -38,7 +38,7 @@ "switch-statement.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -55,7 +55,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 1 @@ -77,9 +77,9 @@ "filePaths": [ "switch-statement.js" ], - "sha1": "cbc2b0ea47a2cd6fb09368f3c72e101f946c4b26", + "sha1": "f5f92d14854e8f589966634672d4609022ac912d", "gitDir": "test/corpus/repos/javascript", - "sha2": "e61491adc3ae0a36743a2fb5a3be26e57637593b" + "sha2": "430a3d8b360e5f9b8ecccddc9ff00ca703814f57" } ,{ "testCaseDescription": "javascript-switch-statement-delete-insert-test", @@ -88,7 +88,7 @@ "switch-statement.js": [ { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -118,7 +118,7 @@ }, { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -153,9 +153,9 @@ "filePaths": [ "switch-statement.js" ], - "sha1": "e61491adc3ae0a36743a2fb5a3be26e57637593b", + "sha1": "430a3d8b360e5f9b8ecccddc9ff00ca703814f57", "gitDir": "test/corpus/repos/javascript", - "sha2": "c62f3ccb77ecb50b8f61d3d058f05a27d4187227" + "sha2": "dd86d549c061ad1000cf990d4056446a70c961cd" } ,{ "testCaseDescription": "javascript-switch-statement-replacement-test", @@ -164,7 +164,7 @@ "switch-statement.js": [ { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -194,7 +194,7 @@ }, { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -229,9 +229,9 @@ "filePaths": [ "switch-statement.js" ], - "sha1": "c62f3ccb77ecb50b8f61d3d058f05a27d4187227", + "sha1": "dd86d549c061ad1000cf990d4056446a70c961cd", "gitDir": "test/corpus/repos/javascript", - "sha2": "08f399fd747b15cef9703dc4f05efd330258e832" + "sha2": "cdb0eb167d6389aa9197e522627b06128c5e6e30" } ,{ "testCaseDescription": "javascript-switch-statement-delete-replacement-test", @@ -240,7 +240,7 @@ "switch-statement.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -257,7 +257,7 @@ }, { "span": { - "this": { + "delete": { "start": [ 2, 1 @@ -274,7 +274,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 1 @@ -296,9 +296,9 @@ "filePaths": [ "switch-statement.js" ], - "sha1": "08f399fd747b15cef9703dc4f05efd330258e832", + "sha1": "cdb0eb167d6389aa9197e522627b06128c5e6e30", "gitDir": "test/corpus/repos/javascript", - "sha2": "100b2392d9286d71b1c1910ddacd28ca2a96284b" + "sha2": "086b2cad74172543d1cec8e29c55aad910c91e9e" } ,{ "testCaseDescription": "javascript-switch-statement-delete-test", @@ -307,7 +307,7 @@ "switch-statement.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -329,9 +329,9 @@ "filePaths": [ "switch-statement.js" ], - "sha1": "100b2392d9286d71b1c1910ddacd28ca2a96284b", + "sha1": "086b2cad74172543d1cec8e29c55aad910c91e9e", "gitDir": "test/corpus/repos/javascript", - "sha2": "f033612791a0f3ff8aa0d4313044903cd7eb8b9a" + "sha2": "17867521083f4d60703aa5cc5c8ff5895d36222b" } ,{ "testCaseDescription": "javascript-switch-statement-delete-rest-test", @@ -340,7 +340,7 @@ "switch-statement.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -362,7 +362,7 @@ "filePaths": [ "switch-statement.js" ], - "sha1": "f033612791a0f3ff8aa0d4313044903cd7eb8b9a", + "sha1": "17867521083f4d60703aa5cc5c8ff5895d36222b", "gitDir": "test/corpus/repos/javascript", - "sha2": "70fe15f33094a3e5dc81081f9bd30e2baa0ff885" + "sha2": "fa5454a8c0278ac9d3451b8e7c780936c149d8a2" }] diff --git a/test/corpus/diff-summaries/javascript/template-string.json b/test/corpus/diff-summaries/javascript/template-string.json index e73ee73f0..bb9af2675 100644 --- a/test/corpus/diff-summaries/javascript/template-string.json +++ b/test/corpus/diff-summaries/javascript/template-string.json @@ -5,7 +5,7 @@ "template-string.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -27,9 +27,9 @@ "filePaths": [ "template-string.js" ], - "sha1": "d3aee735401b2b9c803e3d684ab3c6b96a16898f", + "sha1": "b68fd6fad9ad8bbfb5fef0b97e42bb9899f01a0e", "gitDir": "test/corpus/repos/javascript", - "sha2": "0bf1b7877627bfb8da6474326584c9caaa1b9bf9" + "sha2": "90f174d23bcb10dbc060ff7543e69b0cf69a5279" } ,{ "testCaseDescription": "javascript-template-string-replacement-insert-test", @@ -38,7 +38,7 @@ "template-string.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -55,7 +55,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 1 @@ -77,9 +77,9 @@ "filePaths": [ "template-string.js" ], - "sha1": "0bf1b7877627bfb8da6474326584c9caaa1b9bf9", + "sha1": "90f174d23bcb10dbc060ff7543e69b0cf69a5279", "gitDir": "test/corpus/repos/javascript", - "sha2": "36c95439a521f5cb2a91e8139cf324044e753ac9" + "sha2": "024eb7615d8a0d8a89c72fd12d8a410d8552e78e" } ,{ "testCaseDescription": "javascript-template-string-delete-insert-test", @@ -88,7 +88,7 @@ "template-string.js": [ { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -123,9 +123,9 @@ "filePaths": [ "template-string.js" ], - "sha1": "36c95439a521f5cb2a91e8139cf324044e753ac9", + "sha1": "024eb7615d8a0d8a89c72fd12d8a410d8552e78e", "gitDir": "test/corpus/repos/javascript", - "sha2": "8604dc99b4ccf972649343fdc6a95a17f7823709" + "sha2": "a579cb4d6d75b2ecd6de1eca964770a557872ad3" } ,{ "testCaseDescription": "javascript-template-string-replacement-test", @@ -134,7 +134,7 @@ "template-string.js": [ { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -169,9 +169,9 @@ "filePaths": [ "template-string.js" ], - "sha1": "8604dc99b4ccf972649343fdc6a95a17f7823709", + "sha1": "a579cb4d6d75b2ecd6de1eca964770a557872ad3", "gitDir": "test/corpus/repos/javascript", - "sha2": "ae3d15a910e3f12cb984f003a26e0f1d480c20c4" + "sha2": "0d344fd755f42e0ea79f5f81bc95b0ada2e28c6f" } ,{ "testCaseDescription": "javascript-template-string-delete-replacement-test", @@ -180,7 +180,7 @@ "template-string.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -197,7 +197,7 @@ }, { "span": { - "this": { + "delete": { "start": [ 2, 1 @@ -214,7 +214,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 1 @@ -236,9 +236,9 @@ "filePaths": [ "template-string.js" ], - "sha1": "ae3d15a910e3f12cb984f003a26e0f1d480c20c4", + "sha1": "0d344fd755f42e0ea79f5f81bc95b0ada2e28c6f", "gitDir": "test/corpus/repos/javascript", - "sha2": "857c899c43b360b8e15250c028feb13b37472719" + "sha2": "96ca5ba0f4d011b95915561b4df40eec68e64d88" } ,{ "testCaseDescription": "javascript-template-string-delete-test", @@ -247,7 +247,7 @@ "template-string.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -269,9 +269,9 @@ "filePaths": [ "template-string.js" ], - "sha1": "857c899c43b360b8e15250c028feb13b37472719", + "sha1": "96ca5ba0f4d011b95915561b4df40eec68e64d88", "gitDir": "test/corpus/repos/javascript", - "sha2": "32363666c860768e31d1c805ddee49c819f887a6" + "sha2": "e668d0526b3ad687c13bc4ac0e3b606ff8915184" } ,{ "testCaseDescription": "javascript-template-string-delete-rest-test", @@ -280,7 +280,7 @@ "template-string.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -302,7 +302,7 @@ "filePaths": [ "template-string.js" ], - "sha1": "32363666c860768e31d1c805ddee49c819f887a6", + "sha1": "e668d0526b3ad687c13bc4ac0e3b606ff8915184", "gitDir": "test/corpus/repos/javascript", - "sha2": "67dfbd7b45236e87dcd260ea7ac3c14b307c474f" + "sha2": "17aa0b04103d8aaedf77c3ff72f699f18194a962" }] diff --git a/test/corpus/diff-summaries/javascript/ternary.json b/test/corpus/diff-summaries/javascript/ternary.json index 100ea210d..1f069ee03 100644 --- a/test/corpus/diff-summaries/javascript/ternary.json +++ b/test/corpus/diff-summaries/javascript/ternary.json @@ -5,7 +5,7 @@ "ternary.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -27,9 +27,9 @@ "filePaths": [ "ternary.js" ], - "sha1": "216c9ba07743064780c37d5f07af95a9dee2bf96", + "sha1": "62499db349bd96eba99a785f67d473de8d5b99e6", "gitDir": "test/corpus/repos/javascript", - "sha2": "5a6f3092f70f211e165506d1c3196f24b065f67a" + "sha2": "bc7b9275011e872401a2c3a8c7c17903cdb56169" } ,{ "testCaseDescription": "javascript-ternary-replacement-insert-test", @@ -38,7 +38,7 @@ "ternary.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -55,7 +55,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 1 @@ -77,9 +77,9 @@ "filePaths": [ "ternary.js" ], - "sha1": "5a6f3092f70f211e165506d1c3196f24b065f67a", + "sha1": "bc7b9275011e872401a2c3a8c7c17903cdb56169", "gitDir": "test/corpus/repos/javascript", - "sha2": "b0b8e37ca235cac0f4994d17eb1527cd14e4832b" + "sha2": "b8fea536dd918076cf850567797d069cb7bb324a" } ,{ "testCaseDescription": "javascript-ternary-delete-insert-test", @@ -88,7 +88,7 @@ "ternary.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -105,7 +105,7 @@ }, { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -127,9 +127,9 @@ "filePaths": [ "ternary.js" ], - "sha1": "b0b8e37ca235cac0f4994d17eb1527cd14e4832b", + "sha1": "b8fea536dd918076cf850567797d069cb7bb324a", "gitDir": "test/corpus/repos/javascript", - "sha2": "f7d548f311ce81e47facc215fefc7c734b32f131" + "sha2": "ed0eb4f64eb99a1de0578efbea21954d506b78ad" } ,{ "testCaseDescription": "javascript-ternary-replacement-test", @@ -138,7 +138,7 @@ "ternary.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -155,7 +155,7 @@ }, { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -177,9 +177,9 @@ "filePaths": [ "ternary.js" ], - "sha1": "f7d548f311ce81e47facc215fefc7c734b32f131", + "sha1": "ed0eb4f64eb99a1de0578efbea21954d506b78ad", "gitDir": "test/corpus/repos/javascript", - "sha2": "30da4a7ee5e6eba51591601b2b9ca9cc24d30494" + "sha2": "180368bb326efec93e24d19b6e544eb1c418573b" } ,{ "testCaseDescription": "javascript-ternary-delete-replacement-test", @@ -188,7 +188,7 @@ "ternary.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -205,7 +205,7 @@ }, { "span": { - "this": { + "delete": { "start": [ 2, 1 @@ -222,7 +222,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 1 @@ -244,9 +244,9 @@ "filePaths": [ "ternary.js" ], - "sha1": "30da4a7ee5e6eba51591601b2b9ca9cc24d30494", + "sha1": "180368bb326efec93e24d19b6e544eb1c418573b", "gitDir": "test/corpus/repos/javascript", - "sha2": "9fa12d415964908e661b33756b867eb7616e3d94" + "sha2": "c01612a71ed85281bf9c055ad05b6b7ea76377d5" } ,{ "testCaseDescription": "javascript-ternary-delete-test", @@ -255,7 +255,7 @@ "ternary.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -277,9 +277,9 @@ "filePaths": [ "ternary.js" ], - "sha1": "9fa12d415964908e661b33756b867eb7616e3d94", + "sha1": "c01612a71ed85281bf9c055ad05b6b7ea76377d5", "gitDir": "test/corpus/repos/javascript", - "sha2": "8e6ed77f360e132885b2b329a4d26492a32e0f94" + "sha2": "1d83e7224ad50fbbf8712b8cb674512319d379a0" } ,{ "testCaseDescription": "javascript-ternary-delete-rest-test", @@ -288,7 +288,7 @@ "ternary.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -310,7 +310,7 @@ "filePaths": [ "ternary.js" ], - "sha1": "8e6ed77f360e132885b2b329a4d26492a32e0f94", + "sha1": "1d83e7224ad50fbbf8712b8cb674512319d379a0", "gitDir": "test/corpus/repos/javascript", - "sha2": "3a53bc319251c49799f5e1229514b74297ef88e4" + "sha2": "33ac8949dcc8f9f193b6aec3c6d9a5ef26e4bcfd" }] diff --git a/test/corpus/diff-summaries/javascript/this-expression.json b/test/corpus/diff-summaries/javascript/this-expression.json index af0a0a6ba..f0ac71437 100644 --- a/test/corpus/diff-summaries/javascript/this-expression.json +++ b/test/corpus/diff-summaries/javascript/this-expression.json @@ -5,7 +5,7 @@ "this-expression.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -27,9 +27,9 @@ "filePaths": [ "this-expression.js" ], - "sha1": "324ef3f6d6409ee7a42609453d3259490538a470", + "sha1": "bd9d0d22b6a226d63e44c3d654b6b618571f9912", "gitDir": "test/corpus/repos/javascript", - "sha2": "2823bdb25666f088a22983110b9c71865cd1db71" + "sha2": "9ba0c75c5bc20d8688f51043a458e7d82edf66a7" } ,{ "testCaseDescription": "javascript-this-expression-replacement-insert-test", @@ -38,7 +38,7 @@ "this-expression.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -55,7 +55,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 1 @@ -77,9 +77,9 @@ "filePaths": [ "this-expression.js" ], - "sha1": "2823bdb25666f088a22983110b9c71865cd1db71", + "sha1": "9ba0c75c5bc20d8688f51043a458e7d82edf66a7", "gitDir": "test/corpus/repos/javascript", - "sha2": "754c24295e09df0536bb63de88f45bf9c870e1fb" + "sha2": "6cfe274ee77cd487431fb7a29d6d50cd69ba2582" } ,{ "testCaseDescription": "javascript-this-expression-delete-insert-test", @@ -88,7 +88,7 @@ "this-expression.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -105,7 +105,7 @@ }, { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -127,9 +127,9 @@ "filePaths": [ "this-expression.js" ], - "sha1": "754c24295e09df0536bb63de88f45bf9c870e1fb", + "sha1": "6cfe274ee77cd487431fb7a29d6d50cd69ba2582", "gitDir": "test/corpus/repos/javascript", - "sha2": "ec25a6a159d6bae204a5360b0737325faa2b0f1d" + "sha2": "b03e7c6b77cb36d5bfb953572c32ba9b62fb8f3a" } ,{ "testCaseDescription": "javascript-this-expression-replacement-test", @@ -138,7 +138,7 @@ "this-expression.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -155,7 +155,7 @@ }, { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -177,9 +177,9 @@ "filePaths": [ "this-expression.js" ], - "sha1": "ec25a6a159d6bae204a5360b0737325faa2b0f1d", + "sha1": "b03e7c6b77cb36d5bfb953572c32ba9b62fb8f3a", "gitDir": "test/corpus/repos/javascript", - "sha2": "35fe3d5b2a6524f9c7bbfaa14d4753bd882737b1" + "sha2": "1185333888454aa1868abff45e6110880d636cbe" } ,{ "testCaseDescription": "javascript-this-expression-delete-replacement-test", @@ -188,7 +188,7 @@ "this-expression.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -205,7 +205,7 @@ }, { "span": { - "this": { + "delete": { "start": [ 2, 1 @@ -222,7 +222,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 1 @@ -244,9 +244,9 @@ "filePaths": [ "this-expression.js" ], - "sha1": "35fe3d5b2a6524f9c7bbfaa14d4753bd882737b1", + "sha1": "1185333888454aa1868abff45e6110880d636cbe", "gitDir": "test/corpus/repos/javascript", - "sha2": "cbdcedd3245da3c85c3f88aa5b28f6ec2a61359e" + "sha2": "25b9db8ff255f1f8f8a4b47d7f306a274716fe69" } ,{ "testCaseDescription": "javascript-this-expression-delete-test", @@ -255,7 +255,7 @@ "this-expression.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -277,9 +277,9 @@ "filePaths": [ "this-expression.js" ], - "sha1": "cbdcedd3245da3c85c3f88aa5b28f6ec2a61359e", + "sha1": "25b9db8ff255f1f8f8a4b47d7f306a274716fe69", "gitDir": "test/corpus/repos/javascript", - "sha2": "03fab7b41a417c4a7ba9d0687d775c6036af9794" + "sha2": "381b83d600c8fb17c6fa5ae19c28dd3e02598c84" } ,{ "testCaseDescription": "javascript-this-expression-delete-rest-test", @@ -288,7 +288,7 @@ "this-expression.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -310,7 +310,7 @@ "filePaths": [ "this-expression.js" ], - "sha1": "03fab7b41a417c4a7ba9d0687d775c6036af9794", + "sha1": "381b83d600c8fb17c6fa5ae19c28dd3e02598c84", "gitDir": "test/corpus/repos/javascript", - "sha2": "5e6fd51739eb15db9fcd9e85e7f5c64da736056e" + "sha2": "704c62da36013859dd8e6a1139c4d908e22bc980" }] diff --git a/test/corpus/diff-summaries/javascript/throw-statement.json b/test/corpus/diff-summaries/javascript/throw-statement.json index ed91508cc..6fe00de23 100644 --- a/test/corpus/diff-summaries/javascript/throw-statement.json +++ b/test/corpus/diff-summaries/javascript/throw-statement.json @@ -5,7 +5,7 @@ "throw-statement.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -27,9 +27,9 @@ "filePaths": [ "throw-statement.js" ], - "sha1": "70fe15f33094a3e5dc81081f9bd30e2baa0ff885", + "sha1": "fa5454a8c0278ac9d3451b8e7c780936c149d8a2", "gitDir": "test/corpus/repos/javascript", - "sha2": "16ded5326b4884e9de5e7224f4469f9aae7ecbc8" + "sha2": "344d14d1f0e1c27a17ecbc6b83485f3f06c77496" } ,{ "testCaseDescription": "javascript-throw-statement-replacement-insert-test", @@ -38,7 +38,7 @@ "throw-statement.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -55,7 +55,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 1 @@ -77,9 +77,9 @@ "filePaths": [ "throw-statement.js" ], - "sha1": "16ded5326b4884e9de5e7224f4469f9aae7ecbc8", + "sha1": "344d14d1f0e1c27a17ecbc6b83485f3f06c77496", "gitDir": "test/corpus/repos/javascript", - "sha2": "d848598691d350174c103d649fa429508e293ea9" + "sha2": "34312599d6509f5da3ff900e3b858616aa749b7b" } ,{ "testCaseDescription": "javascript-throw-statement-delete-insert-test", @@ -88,7 +88,7 @@ "throw-statement.js": [ { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -123,9 +123,9 @@ "filePaths": [ "throw-statement.js" ], - "sha1": "d848598691d350174c103d649fa429508e293ea9", + "sha1": "34312599d6509f5da3ff900e3b858616aa749b7b", "gitDir": "test/corpus/repos/javascript", - "sha2": "2501b7502e6a944405259269fec5f99b807856c8" + "sha2": "22a1fffadbd913d4ca3e0eb3d628255ff7b0b380" } ,{ "testCaseDescription": "javascript-throw-statement-replacement-test", @@ -134,7 +134,7 @@ "throw-statement.js": [ { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -169,9 +169,9 @@ "filePaths": [ "throw-statement.js" ], - "sha1": "2501b7502e6a944405259269fec5f99b807856c8", + "sha1": "22a1fffadbd913d4ca3e0eb3d628255ff7b0b380", "gitDir": "test/corpus/repos/javascript", - "sha2": "6172a941a9627baa0c7ece469436e3d7eb5e41de" + "sha2": "a1cd4e7888a7de32aa49e8267348dc595235e201" } ,{ "testCaseDescription": "javascript-throw-statement-delete-replacement-test", @@ -180,7 +180,7 @@ "throw-statement.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -197,7 +197,7 @@ }, { "span": { - "this": { + "delete": { "start": [ 2, 1 @@ -214,7 +214,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 1 @@ -236,9 +236,9 @@ "filePaths": [ "throw-statement.js" ], - "sha1": "6172a941a9627baa0c7ece469436e3d7eb5e41de", + "sha1": "a1cd4e7888a7de32aa49e8267348dc595235e201", "gitDir": "test/corpus/repos/javascript", - "sha2": "9d70a68cc287b4ad90075701308eca5c1cd843f1" + "sha2": "2fb4baa71ca7aeb0ce7b0321b30d926b0a5d3dbf" } ,{ "testCaseDescription": "javascript-throw-statement-delete-test", @@ -247,7 +247,7 @@ "throw-statement.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -269,9 +269,9 @@ "filePaths": [ "throw-statement.js" ], - "sha1": "9d70a68cc287b4ad90075701308eca5c1cd843f1", + "sha1": "2fb4baa71ca7aeb0ce7b0321b30d926b0a5d3dbf", "gitDir": "test/corpus/repos/javascript", - "sha2": "807015730993ae0d3e28ddd0b06d20b9adf12492" + "sha2": "15037656787410bc4177feb4be3ecd795cd600d4" } ,{ "testCaseDescription": "javascript-throw-statement-delete-rest-test", @@ -280,7 +280,7 @@ "throw-statement.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -302,7 +302,7 @@ "filePaths": [ "throw-statement.js" ], - "sha1": "807015730993ae0d3e28ddd0b06d20b9adf12492", + "sha1": "15037656787410bc4177feb4be3ecd795cd600d4", "gitDir": "test/corpus/repos/javascript", - "sha2": "eb8ac03b17e740cb895c1e398a23ece6b7108422" + "sha2": "fec91a78934dfbf56bb06aa17dfe6d908bf7555f" }] diff --git a/test/corpus/diff-summaries/javascript/true.json b/test/corpus/diff-summaries/javascript/true.json index 626325496..f47e90b49 100644 --- a/test/corpus/diff-summaries/javascript/true.json +++ b/test/corpus/diff-summaries/javascript/true.json @@ -5,7 +5,7 @@ "true.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -27,9 +27,9 @@ "filePaths": [ "true.js" ], - "sha1": "1629fb4f8707806f5be1e2cef413d2b828064f0b", + "sha1": "d75865051390be293044f1901b2de814f883345c", "gitDir": "test/corpus/repos/javascript", - "sha2": "94cc02f4e6099bf670e487a67e0b4d780932f2cf" + "sha2": "6bfb7dcd9cdede9f50d88268469edcc41bf7a011" } ,{ "testCaseDescription": "javascript-true-replacement-insert-test", @@ -38,7 +38,7 @@ "true.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -55,7 +55,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 1 @@ -77,9 +77,9 @@ "filePaths": [ "true.js" ], - "sha1": "94cc02f4e6099bf670e487a67e0b4d780932f2cf", + "sha1": "6bfb7dcd9cdede9f50d88268469edcc41bf7a011", "gitDir": "test/corpus/repos/javascript", - "sha2": "356f076ff1abcc3dd92cf1a55175b4fa93736565" + "sha2": "2fb11e227c29c8708462b86607f5898a1526411d" } ,{ "testCaseDescription": "javascript-true-delete-insert-test", @@ -88,7 +88,7 @@ "true.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -105,7 +105,7 @@ }, { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -127,9 +127,9 @@ "filePaths": [ "true.js" ], - "sha1": "356f076ff1abcc3dd92cf1a55175b4fa93736565", + "sha1": "2fb11e227c29c8708462b86607f5898a1526411d", "gitDir": "test/corpus/repos/javascript", - "sha2": "9581e3270470aac80cd09c9512dab08e0aebc733" + "sha2": "44fd30110d94eb034134620ce0043421555609ba" } ,{ "testCaseDescription": "javascript-true-replacement-test", @@ -138,7 +138,7 @@ "true.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -155,7 +155,7 @@ }, { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -177,9 +177,9 @@ "filePaths": [ "true.js" ], - "sha1": "9581e3270470aac80cd09c9512dab08e0aebc733", + "sha1": "44fd30110d94eb034134620ce0043421555609ba", "gitDir": "test/corpus/repos/javascript", - "sha2": "561495b8d383328d5e897ddda7e1faba194f69ae" + "sha2": "865858a52fcb1b2b3425b9edbcfd46170997267f" } ,{ "testCaseDescription": "javascript-true-delete-replacement-test", @@ -188,7 +188,7 @@ "true.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -205,7 +205,7 @@ }, { "span": { - "this": { + "delete": { "start": [ 2, 1 @@ -222,7 +222,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 1 @@ -244,9 +244,9 @@ "filePaths": [ "true.js" ], - "sha1": "561495b8d383328d5e897ddda7e1faba194f69ae", + "sha1": "865858a52fcb1b2b3425b9edbcfd46170997267f", "gitDir": "test/corpus/repos/javascript", - "sha2": "471d26ce0f0e66973181d3912a27a619ad3a8795" + "sha2": "61cd6e15c4e041ff8aa683707a4540122de8560c" } ,{ "testCaseDescription": "javascript-true-delete-test", @@ -255,7 +255,7 @@ "true.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -277,9 +277,9 @@ "filePaths": [ "true.js" ], - "sha1": "471d26ce0f0e66973181d3912a27a619ad3a8795", + "sha1": "61cd6e15c4e041ff8aa683707a4540122de8560c", "gitDir": "test/corpus/repos/javascript", - "sha2": "e6498022517e3044ed8c9cd284c82ace50342a7c" + "sha2": "eddb50d6d415cae98a46191354bc339a1a9634f3" } ,{ "testCaseDescription": "javascript-true-delete-rest-test", @@ -288,7 +288,7 @@ "true.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -310,7 +310,7 @@ "filePaths": [ "true.js" ], - "sha1": "e6498022517e3044ed8c9cd284c82ace50342a7c", + "sha1": "eddb50d6d415cae98a46191354bc339a1a9634f3", "gitDir": "test/corpus/repos/javascript", - "sha2": "2729ff0e359b38bda1f650d3283d4116dc2fa3ad" + "sha2": "0cad1bc8f133de3ec0a2bff083b413422673bbb7" }] diff --git a/test/corpus/diff-summaries/javascript/try-statement.json b/test/corpus/diff-summaries/javascript/try-statement.json index a2f9426d7..4fba79e1b 100644 --- a/test/corpus/diff-summaries/javascript/try-statement.json +++ b/test/corpus/diff-summaries/javascript/try-statement.json @@ -5,7 +5,7 @@ "try-statement.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -27,9 +27,9 @@ "filePaths": [ "try-statement.js" ], - "sha1": "eb8ac03b17e740cb895c1e398a23ece6b7108422", + "sha1": "fec91a78934dfbf56bb06aa17dfe6d908bf7555f", "gitDir": "test/corpus/repos/javascript", - "sha2": "5934d5c231a7d9ae7cbe9b332296d7b6d82b59df" + "sha2": "d4e5fd15a738e341a8e5f579a038aefb05b9ccdf" } ,{ "testCaseDescription": "javascript-try-statement-replacement-insert-test", @@ -38,7 +38,7 @@ "try-statement.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -55,7 +55,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 1 @@ -77,9 +77,9 @@ "filePaths": [ "try-statement.js" ], - "sha1": "5934d5c231a7d9ae7cbe9b332296d7b6d82b59df", + "sha1": "d4e5fd15a738e341a8e5f579a038aefb05b9ccdf", "gitDir": "test/corpus/repos/javascript", - "sha2": "f0ea450f12fa45c3ce41f2f8178719797116a3bb" + "sha2": "3c0e74e309438cf7cd12e56be343f89f03398ae4" } ,{ "testCaseDescription": "javascript-try-statement-delete-insert-test", @@ -88,7 +88,7 @@ "try-statement.js": [ { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -118,7 +118,7 @@ }, { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -153,9 +153,9 @@ "filePaths": [ "try-statement.js" ], - "sha1": "f0ea450f12fa45c3ce41f2f8178719797116a3bb", + "sha1": "3c0e74e309438cf7cd12e56be343f89f03398ae4", "gitDir": "test/corpus/repos/javascript", - "sha2": "1995a3278e3b1009112f4b37f8c0d9215f81468c" + "sha2": "1320684e440745541c94b72e325582231c7baf15" } ,{ "testCaseDescription": "javascript-try-statement-replacement-test", @@ -164,7 +164,7 @@ "try-statement.js": [ { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -194,7 +194,7 @@ }, { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -229,9 +229,9 @@ "filePaths": [ "try-statement.js" ], - "sha1": "1995a3278e3b1009112f4b37f8c0d9215f81468c", + "sha1": "1320684e440745541c94b72e325582231c7baf15", "gitDir": "test/corpus/repos/javascript", - "sha2": "031540f54220001ba27ec1c6f7f573d5c360c0a3" + "sha2": "770982b7c0e824221296f6aaa73df8284fd754ca" } ,{ "testCaseDescription": "javascript-try-statement-delete-replacement-test", @@ -240,7 +240,7 @@ "try-statement.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -257,7 +257,7 @@ }, { "span": { - "this": { + "delete": { "start": [ 2, 1 @@ -274,7 +274,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 1 @@ -296,9 +296,9 @@ "filePaths": [ "try-statement.js" ], - "sha1": "031540f54220001ba27ec1c6f7f573d5c360c0a3", + "sha1": "770982b7c0e824221296f6aaa73df8284fd754ca", "gitDir": "test/corpus/repos/javascript", - "sha2": "1f15321135b2625ac1f1ac294f56d03ca22bf3e4" + "sha2": "0b1a36ea037d3725f562207d094f1cfb388a90fc" } ,{ "testCaseDescription": "javascript-try-statement-delete-test", @@ -307,7 +307,7 @@ "try-statement.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -329,9 +329,9 @@ "filePaths": [ "try-statement.js" ], - "sha1": "1f15321135b2625ac1f1ac294f56d03ca22bf3e4", + "sha1": "0b1a36ea037d3725f562207d094f1cfb388a90fc", "gitDir": "test/corpus/repos/javascript", - "sha2": "19bdd1121f08b296b9c29125cc2ce914b97eec82" + "sha2": "0606bc7af03d60fa3b6f7b564b207ff540ccda67" } ,{ "testCaseDescription": "javascript-try-statement-delete-rest-test", @@ -340,7 +340,7 @@ "try-statement.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -362,7 +362,7 @@ "filePaths": [ "try-statement.js" ], - "sha1": "19bdd1121f08b296b9c29125cc2ce914b97eec82", + "sha1": "0606bc7af03d60fa3b6f7b564b207ff540ccda67", "gitDir": "test/corpus/repos/javascript", - "sha2": "a23b0a588d860380edd5b815810c34e35d5855a8" + "sha2": "1980a80ff9a2f2886b85d2e8ce9df29b1f7adad5" }] diff --git a/test/corpus/diff-summaries/javascript/type-operator.json b/test/corpus/diff-summaries/javascript/type-operator.json index cdef1b2ae..73a18c824 100644 --- a/test/corpus/diff-summaries/javascript/type-operator.json +++ b/test/corpus/diff-summaries/javascript/type-operator.json @@ -5,7 +5,7 @@ "type-operator.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -27,9 +27,9 @@ "filePaths": [ "type-operator.js" ], - "sha1": "3a53bc319251c49799f5e1229514b74297ef88e4", + "sha1": "33ac8949dcc8f9f193b6aec3c6d9a5ef26e4bcfd", "gitDir": "test/corpus/repos/javascript", - "sha2": "88f1751f62f6e08907661f4817436a3686c1db71" + "sha2": "c834305365c2c583d268ac9da622e6970389c792" } ,{ "testCaseDescription": "javascript-type-operator-replacement-insert-test", @@ -38,7 +38,7 @@ "type-operator.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -55,7 +55,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 1 @@ -77,9 +77,9 @@ "filePaths": [ "type-operator.js" ], - "sha1": "88f1751f62f6e08907661f4817436a3686c1db71", + "sha1": "c834305365c2c583d268ac9da622e6970389c792", "gitDir": "test/corpus/repos/javascript", - "sha2": "2dbfcfa73dbc738e8b2194799fb7d737f5cbf32c" + "sha2": "ec2fb13d8e616b8ec628e5218c4bb18ca8b4cd24" } ,{ "testCaseDescription": "javascript-type-operator-delete-insert-test", @@ -88,7 +88,7 @@ "type-operator.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 14 @@ -110,9 +110,9 @@ "filePaths": [ "type-operator.js" ], - "sha1": "2dbfcfa73dbc738e8b2194799fb7d737f5cbf32c", + "sha1": "ec2fb13d8e616b8ec628e5218c4bb18ca8b4cd24", "gitDir": "test/corpus/repos/javascript", - "sha2": "01a5f643661510a0da476bfa9dcd740b35417497" + "sha2": "eb132ce69c3cb4c687bb161634bc0bdb55a8e564" } ,{ "testCaseDescription": "javascript-type-operator-replacement-test", @@ -121,7 +121,7 @@ "type-operator.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 14 @@ -143,9 +143,9 @@ "filePaths": [ "type-operator.js" ], - "sha1": "01a5f643661510a0da476bfa9dcd740b35417497", + "sha1": "eb132ce69c3cb4c687bb161634bc0bdb55a8e564", "gitDir": "test/corpus/repos/javascript", - "sha2": "d1c04495339ea50e222bf286dcba37f841623773" + "sha2": "5c79344eafe1434fb72000c8bfd8bfe22bc990f1" } ,{ "testCaseDescription": "javascript-type-operator-delete-replacement-test", @@ -154,7 +154,7 @@ "type-operator.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -171,7 +171,7 @@ }, { "span": { - "this": { + "delete": { "start": [ 2, 1 @@ -188,7 +188,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 1 @@ -210,9 +210,9 @@ "filePaths": [ "type-operator.js" ], - "sha1": "d1c04495339ea50e222bf286dcba37f841623773", + "sha1": "5c79344eafe1434fb72000c8bfd8bfe22bc990f1", "gitDir": "test/corpus/repos/javascript", - "sha2": "df838082db78f590e0fe548d501573688c41e6e6" + "sha2": "1ae514fd9d6e3188404301b117cd0e0bbefd5ed3" } ,{ "testCaseDescription": "javascript-type-operator-delete-test", @@ -221,7 +221,7 @@ "type-operator.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -243,9 +243,9 @@ "filePaths": [ "type-operator.js" ], - "sha1": "df838082db78f590e0fe548d501573688c41e6e6", + "sha1": "1ae514fd9d6e3188404301b117cd0e0bbefd5ed3", "gitDir": "test/corpus/repos/javascript", - "sha2": "a4c2f82fa95065ae07a082ab5cac594e41e552db" + "sha2": "5d4e55e8afed2e391c912eb255564ec581205e42" } ,{ "testCaseDescription": "javascript-type-operator-delete-rest-test", @@ -254,7 +254,7 @@ "type-operator.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -276,7 +276,7 @@ "filePaths": [ "type-operator.js" ], - "sha1": "a4c2f82fa95065ae07a082ab5cac594e41e552db", + "sha1": "5d4e55e8afed2e391c912eb255564ec581205e42", "gitDir": "test/corpus/repos/javascript", - "sha2": "215414e0397973e2f7d49a8edff9cf1d84fad02a" + "sha2": "ba1f4c979646df1521e9a187cc24c8b8afc3cd24" }] diff --git a/test/corpus/diff-summaries/javascript/undefined.json b/test/corpus/diff-summaries/javascript/undefined.json index ea0245846..b290056b7 100644 --- a/test/corpus/diff-summaries/javascript/undefined.json +++ b/test/corpus/diff-summaries/javascript/undefined.json @@ -5,7 +5,7 @@ "undefined.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -27,9 +27,9 @@ "filePaths": [ "undefined.js" ], - "sha1": "0cf324666c04ffe5413f3e03ff09dc4a3883ab7c", + "sha1": "660e3a5b95669c843b77a62446f2e57dcde9e285", "gitDir": "test/corpus/repos/javascript", - "sha2": "903a9a541686eb72e2368433c52c1629471946bb" + "sha2": "c2db3416e7367c32a0fe0ec5ba7f39f1392205f5" } ,{ "testCaseDescription": "javascript-undefined-replacement-insert-test", @@ -38,7 +38,7 @@ "undefined.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -55,7 +55,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 1 @@ -77,9 +77,9 @@ "filePaths": [ "undefined.js" ], - "sha1": "903a9a541686eb72e2368433c52c1629471946bb", + "sha1": "c2db3416e7367c32a0fe0ec5ba7f39f1392205f5", "gitDir": "test/corpus/repos/javascript", - "sha2": "ad1a018329b77e1b61390ecf5e41ac819621092f" + "sha2": "849f2668e8c0eb5cad7c9f2013b8260b9b307a70" } ,{ "testCaseDescription": "javascript-undefined-delete-insert-test", @@ -88,7 +88,7 @@ "undefined.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -105,7 +105,7 @@ }, { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -127,9 +127,9 @@ "filePaths": [ "undefined.js" ], - "sha1": "ad1a018329b77e1b61390ecf5e41ac819621092f", + "sha1": "849f2668e8c0eb5cad7c9f2013b8260b9b307a70", "gitDir": "test/corpus/repos/javascript", - "sha2": "b7e10abedf4f7deda145e91e0462dbe4c1a9956c" + "sha2": "0a811ae8a68a68c4a1641626085a5190d0a67291" } ,{ "testCaseDescription": "javascript-undefined-replacement-test", @@ -138,7 +138,7 @@ "undefined.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -155,7 +155,7 @@ }, { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -177,9 +177,9 @@ "filePaths": [ "undefined.js" ], - "sha1": "b7e10abedf4f7deda145e91e0462dbe4c1a9956c", + "sha1": "0a811ae8a68a68c4a1641626085a5190d0a67291", "gitDir": "test/corpus/repos/javascript", - "sha2": "bd83760f930bd0e4710cb3a9f66c682417a36ed8" + "sha2": "aff5794717cafa1f3c88d9f5062f6df035f1e376" } ,{ "testCaseDescription": "javascript-undefined-delete-replacement-test", @@ -188,7 +188,7 @@ "undefined.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -205,7 +205,7 @@ }, { "span": { - "this": { + "delete": { "start": [ 2, 1 @@ -222,7 +222,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 1 @@ -244,9 +244,9 @@ "filePaths": [ "undefined.js" ], - "sha1": "bd83760f930bd0e4710cb3a9f66c682417a36ed8", + "sha1": "aff5794717cafa1f3c88d9f5062f6df035f1e376", "gitDir": "test/corpus/repos/javascript", - "sha2": "5ad97c97a2128df95602077d624479ec65a04124" + "sha2": "338f22f3617197c3dd81916ddf03e890901a413e" } ,{ "testCaseDescription": "javascript-undefined-delete-test", @@ -255,7 +255,7 @@ "undefined.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -277,9 +277,9 @@ "filePaths": [ "undefined.js" ], - "sha1": "5ad97c97a2128df95602077d624479ec65a04124", + "sha1": "338f22f3617197c3dd81916ddf03e890901a413e", "gitDir": "test/corpus/repos/javascript", - "sha2": "1ba67fdc33e9717a6b1aa69e380897fed2a034e7" + "sha2": "91fe56f6791949afc929cddd8654bd51b38746cf" } ,{ "testCaseDescription": "javascript-undefined-delete-rest-test", @@ -288,7 +288,7 @@ "undefined.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -310,7 +310,7 @@ "filePaths": [ "undefined.js" ], - "sha1": "1ba67fdc33e9717a6b1aa69e380897fed2a034e7", + "sha1": "91fe56f6791949afc929cddd8654bd51b38746cf", "gitDir": "test/corpus/repos/javascript", - "sha2": "1629fb4f8707806f5be1e2cef413d2b828064f0b" + "sha2": "d75865051390be293044f1901b2de814f883345c" }] diff --git a/test/corpus/diff-summaries/javascript/var-declaration.json b/test/corpus/diff-summaries/javascript/var-declaration.json index be928d8ac..37f08111e 100644 --- a/test/corpus/diff-summaries/javascript/var-declaration.json +++ b/test/corpus/diff-summaries/javascript/var-declaration.json @@ -5,7 +5,7 @@ "var-declaration.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 5 @@ -27,9 +27,9 @@ "filePaths": [ "var-declaration.js" ], - "sha1": "b9adfaa1ed76ab8073a888953b9f52ed07ae901d", + "sha1": "07e2e44f7f0b200f4b3454b91a777075ca8a6bf6", "gitDir": "test/corpus/repos/javascript", - "sha2": "e7fb4ec50d4b102631cb919440f306001a37e6dc" + "sha2": "64fc6fb51d210079cd9afabc5f566604f46e35ba" } ,{ "testCaseDescription": "javascript-var-declaration-replacement-insert-test", @@ -38,7 +38,7 @@ "var-declaration.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 5 @@ -55,7 +55,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 1, 8 @@ -72,7 +72,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 1, 16 @@ -89,7 +89,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 5 @@ -111,9 +111,9 @@ "filePaths": [ "var-declaration.js" ], - "sha1": "e7fb4ec50d4b102631cb919440f306001a37e6dc", + "sha1": "64fc6fb51d210079cd9afabc5f566604f46e35ba", "gitDir": "test/corpus/repos/javascript", - "sha2": "64e82b7c2ba46e720224dd265772025e78cb70b7" + "sha2": "eab71c8144bb1445bb263d7d7dd6ba0f8728b047" } ,{ "testCaseDescription": "javascript-var-declaration-delete-insert-test", @@ -122,7 +122,7 @@ "var-declaration.js": [ { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -152,7 +152,7 @@ }, { "span": { - "this": { + "delete": { "start": [ 1, 8 @@ -169,7 +169,7 @@ }, { "span": { - "this": { + "delete": { "start": [ 1, 16 @@ -191,9 +191,9 @@ "filePaths": [ "var-declaration.js" ], - "sha1": "64e82b7c2ba46e720224dd265772025e78cb70b7", + "sha1": "eab71c8144bb1445bb263d7d7dd6ba0f8728b047", "gitDir": "test/corpus/repos/javascript", - "sha2": "483b3edb575f17ee20c8211977b74f5cb16d0be0" + "sha2": "9ffe00e034939d94a0270d072e6cb6ab6fbce75a" } ,{ "testCaseDescription": "javascript-var-declaration-replacement-test", @@ -202,7 +202,7 @@ "var-declaration.js": [ { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -232,7 +232,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 1, 8 @@ -249,7 +249,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 1, 16 @@ -271,9 +271,9 @@ "filePaths": [ "var-declaration.js" ], - "sha1": "483b3edb575f17ee20c8211977b74f5cb16d0be0", + "sha1": "9ffe00e034939d94a0270d072e6cb6ab6fbce75a", "gitDir": "test/corpus/repos/javascript", - "sha2": "205c09348c66d5fece285d675cf454357adb5493" + "sha2": "e82d5c901f5e471b3f531fd989751b7c5e797b66" } ,{ "testCaseDescription": "javascript-var-declaration-delete-replacement-test", @@ -282,7 +282,7 @@ "var-declaration.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 5 @@ -299,7 +299,7 @@ }, { "span": { - "this": { + "delete": { "start": [ 1, 8 @@ -316,7 +316,7 @@ }, { "span": { - "this": { + "delete": { "start": [ 1, 16 @@ -333,7 +333,7 @@ }, { "span": { - "this": { + "delete": { "start": [ 2, 5 @@ -350,7 +350,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 5 @@ -367,7 +367,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 8 @@ -384,7 +384,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 16 @@ -406,9 +406,9 @@ "filePaths": [ "var-declaration.js" ], - "sha1": "205c09348c66d5fece285d675cf454357adb5493", + "sha1": "e82d5c901f5e471b3f531fd989751b7c5e797b66", "gitDir": "test/corpus/repos/javascript", - "sha2": "d7d8aa3680790caf2b3c5140a3bf7dac3db9d341" + "sha2": "35e9e019656681c243e258f38680af210ea248f3" } ,{ "testCaseDescription": "javascript-var-declaration-delete-test", @@ -417,7 +417,7 @@ "var-declaration.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 5 @@ -439,9 +439,9 @@ "filePaths": [ "var-declaration.js" ], - "sha1": "d7d8aa3680790caf2b3c5140a3bf7dac3db9d341", + "sha1": "35e9e019656681c243e258f38680af210ea248f3", "gitDir": "test/corpus/repos/javascript", - "sha2": "71422bb2b7a22e8005be0975966a8b8aecab9acb" + "sha2": "8e88238b5e011419977e6fa14d97be8d1c744002" } ,{ "testCaseDescription": "javascript-var-declaration-delete-rest-test", @@ -450,7 +450,7 @@ "var-declaration.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 5 @@ -467,7 +467,7 @@ }, { "span": { - "this": { + "delete": { "start": [ 1, 8 @@ -484,7 +484,7 @@ }, { "span": { - "this": { + "delete": { "start": [ 1, 16 @@ -506,7 +506,7 @@ "filePaths": [ "var-declaration.js" ], - "sha1": "71422bb2b7a22e8005be0975966a8b8aecab9acb", + "sha1": "8e88238b5e011419977e6fa14d97be8d1c744002", "gitDir": "test/corpus/repos/javascript", - "sha2": "72fe137f23a68d773c76719f790807ead00ef84a" + "sha2": "7c4be6139148ad009e9bf49df1952b9abe45aee0" }] diff --git a/test/corpus/diff-summaries/javascript/variable.json b/test/corpus/diff-summaries/javascript/variable.json index 81087dddf..3556124f7 100644 --- a/test/corpus/diff-summaries/javascript/variable.json +++ b/test/corpus/diff-summaries/javascript/variable.json @@ -5,7 +5,7 @@ "variable.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -27,9 +27,9 @@ "filePaths": [ "variable.js" ], - "sha1": "45a6d97047c9425f56128ec4e4400027be11cad7", + "sha1": "6539b8361c59312164d8321ca3888c0511fcf849", "gitDir": "test/corpus/repos/javascript", - "sha2": "9dad141263720dcf07ceb13d01029c69bcef38ea" + "sha2": "c0e6c0ded2a3dced105d1ab80857cc20258b07ae" } ,{ "testCaseDescription": "javascript-variable-replacement-insert-test", @@ -38,7 +38,7 @@ "variable.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -55,7 +55,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 1 @@ -77,9 +77,9 @@ "filePaths": [ "variable.js" ], - "sha1": "9dad141263720dcf07ceb13d01029c69bcef38ea", + "sha1": "c0e6c0ded2a3dced105d1ab80857cc20258b07ae", "gitDir": "test/corpus/repos/javascript", - "sha2": "4f6333428bf9465cdab6df21470f1787d3bff8d7" + "sha2": "2de090754d832844bf03836c5e571ab5cad2e084" } ,{ "testCaseDescription": "javascript-variable-delete-insert-test", @@ -88,7 +88,7 @@ "variable.js": [ { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -123,9 +123,9 @@ "filePaths": [ "variable.js" ], - "sha1": "4f6333428bf9465cdab6df21470f1787d3bff8d7", + "sha1": "2de090754d832844bf03836c5e571ab5cad2e084", "gitDir": "test/corpus/repos/javascript", - "sha2": "f5e4df4fc4b3baf6dabfad4aee94248f5ba36189" + "sha2": "0f970d0d8f050af10bc4c12aaf36ffa4f13f8b2d" } ,{ "testCaseDescription": "javascript-variable-replacement-test", @@ -134,7 +134,7 @@ "variable.js": [ { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -169,9 +169,9 @@ "filePaths": [ "variable.js" ], - "sha1": "f5e4df4fc4b3baf6dabfad4aee94248f5ba36189", + "sha1": "0f970d0d8f050af10bc4c12aaf36ffa4f13f8b2d", "gitDir": "test/corpus/repos/javascript", - "sha2": "6c86ef3484ecc568dfff6dc7d6bf603ac8dc8fcd" + "sha2": "adf96a48ac5436cb72483251db0f21b1f6c0628e" } ,{ "testCaseDescription": "javascript-variable-delete-replacement-test", @@ -180,7 +180,7 @@ "variable.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -197,7 +197,7 @@ }, { "span": { - "this": { + "delete": { "start": [ 2, 1 @@ -214,7 +214,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 1 @@ -236,9 +236,9 @@ "filePaths": [ "variable.js" ], - "sha1": "6c86ef3484ecc568dfff6dc7d6bf603ac8dc8fcd", + "sha1": "adf96a48ac5436cb72483251db0f21b1f6c0628e", "gitDir": "test/corpus/repos/javascript", - "sha2": "a41e6666d1ea0ed4c08217d4aa16d53fcde04f5e" + "sha2": "51ba6b7b1c97e55fd7608918ac7bf9b5b4b986cd" } ,{ "testCaseDescription": "javascript-variable-delete-test", @@ -247,7 +247,7 @@ "variable.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -269,9 +269,9 @@ "filePaths": [ "variable.js" ], - "sha1": "a41e6666d1ea0ed4c08217d4aa16d53fcde04f5e", + "sha1": "51ba6b7b1c97e55fd7608918ac7bf9b5b4b986cd", "gitDir": "test/corpus/repos/javascript", - "sha2": "dbf27da132fca11e0fd7163c0bc5583fdd85f37c" + "sha2": "04b1ca5574c5256d2d3db1d073308ff0ce040736" } ,{ "testCaseDescription": "javascript-variable-delete-rest-test", @@ -280,7 +280,7 @@ "variable.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -302,7 +302,7 @@ "filePaths": [ "variable.js" ], - "sha1": "dbf27da132fca11e0fd7163c0bc5583fdd85f37c", + "sha1": "04b1ca5574c5256d2d3db1d073308ff0ce040736", "gitDir": "test/corpus/repos/javascript", - "sha2": "1917c441d2b5dc77f63539a5df1e3cd7f0df97f3" + "sha2": "e8164f9a5c7441db5367d1dee13694204e67e3ab" }] diff --git a/test/corpus/diff-summaries/javascript/void-operator.json b/test/corpus/diff-summaries/javascript/void-operator.json index 49339ba0b..e70464ca0 100644 --- a/test/corpus/diff-summaries/javascript/void-operator.json +++ b/test/corpus/diff-summaries/javascript/void-operator.json @@ -5,7 +5,7 @@ "void-operator.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -27,9 +27,9 @@ "filePaths": [ "void-operator.js" ], - "sha1": "9dd33ff948d47044417ab8a6cb2dd82903a8a1b4", + "sha1": "9b9215fdd0036d2a74bfc6a6c4b43187e3ad3ef8", "gitDir": "test/corpus/repos/javascript", - "sha2": "b0f3ec4fd9d9fd71059a3ae6e64697c1f9fb7d15" + "sha2": "88f904cc009da2f43118249073884d11224bf555" } ,{ "testCaseDescription": "javascript-void-operator-replacement-insert-test", @@ -38,7 +38,7 @@ "void-operator.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -55,7 +55,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 1 @@ -77,9 +77,9 @@ "filePaths": [ "void-operator.js" ], - "sha1": "b0f3ec4fd9d9fd71059a3ae6e64697c1f9fb7d15", + "sha1": "88f904cc009da2f43118249073884d11224bf555", "gitDir": "test/corpus/repos/javascript", - "sha2": "90c01b59c54d23c04146dda988090b77a29ed5bb" + "sha2": "65a805f7fe2111b798cc226fbf085c406fb00126" } ,{ "testCaseDescription": "javascript-void-operator-delete-insert-test", @@ -88,7 +88,7 @@ "void-operator.js": [ { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -123,9 +123,9 @@ "filePaths": [ "void-operator.js" ], - "sha1": "90c01b59c54d23c04146dda988090b77a29ed5bb", + "sha1": "65a805f7fe2111b798cc226fbf085c406fb00126", "gitDir": "test/corpus/repos/javascript", - "sha2": "7a4959d77283a38b9e8b8c12dba589465b0fb8f2" + "sha2": "f099f306c71ccab2f86105d2f2d9a9d1ce6211b7" } ,{ "testCaseDescription": "javascript-void-operator-replacement-test", @@ -134,7 +134,7 @@ "void-operator.js": [ { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -169,9 +169,9 @@ "filePaths": [ "void-operator.js" ], - "sha1": "7a4959d77283a38b9e8b8c12dba589465b0fb8f2", + "sha1": "f099f306c71ccab2f86105d2f2d9a9d1ce6211b7", "gitDir": "test/corpus/repos/javascript", - "sha2": "8354c0746eacdabc13749e42dc63fad7bfb50a93" + "sha2": "c5c1f0f74dee37333fdd1202752d9bea669d1bcc" } ,{ "testCaseDescription": "javascript-void-operator-delete-replacement-test", @@ -180,7 +180,7 @@ "void-operator.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -197,7 +197,7 @@ }, { "span": { - "this": { + "delete": { "start": [ 2, 1 @@ -214,7 +214,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 1 @@ -236,9 +236,9 @@ "filePaths": [ "void-operator.js" ], - "sha1": "8354c0746eacdabc13749e42dc63fad7bfb50a93", + "sha1": "c5c1f0f74dee37333fdd1202752d9bea669d1bcc", "gitDir": "test/corpus/repos/javascript", - "sha2": "0b94a16d84a2dad46c1e6dc0a865da9b5c88c70f" + "sha2": "db4b02eb917d57894ba5712873b4cad0d5741cbc" } ,{ "testCaseDescription": "javascript-void-operator-delete-test", @@ -247,7 +247,7 @@ "void-operator.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -269,9 +269,9 @@ "filePaths": [ "void-operator.js" ], - "sha1": "0b94a16d84a2dad46c1e6dc0a865da9b5c88c70f", + "sha1": "db4b02eb917d57894ba5712873b4cad0d5741cbc", "gitDir": "test/corpus/repos/javascript", - "sha2": "27c04d4aef34178ffa822edd57c607fa3ff5ce03" + "sha2": "b09908d0eaf50a489bab70fcd8a734a2553f97e8" } ,{ "testCaseDescription": "javascript-void-operator-delete-rest-test", @@ -280,7 +280,7 @@ "void-operator.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -302,7 +302,7 @@ "filePaths": [ "void-operator.js" ], - "sha1": "27c04d4aef34178ffa822edd57c607fa3ff5ce03", + "sha1": "b09908d0eaf50a489bab70fcd8a734a2553f97e8", "gitDir": "test/corpus/repos/javascript", - "sha2": "d1711a33e14ac0a6c516afdd4885511a60f6a194" + "sha2": "7a5a7e14fdfb56a4dae67672a83aceb49d90f6bf" }] diff --git a/test/corpus/diff-summaries/javascript/while-statement.json b/test/corpus/diff-summaries/javascript/while-statement.json index fa3201697..25f05e2eb 100644 --- a/test/corpus/diff-summaries/javascript/while-statement.json +++ b/test/corpus/diff-summaries/javascript/while-statement.json @@ -5,7 +5,7 @@ "while-statement.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -27,9 +27,9 @@ "filePaths": [ "while-statement.js" ], - "sha1": "7f97f2e3a13baab2548b10a72e291b71ca0b9fa4", + "sha1": "1cbcc1b45ee2afdae4047efbc3ee0f15e89e3394", "gitDir": "test/corpus/repos/javascript", - "sha2": "9704581566ea216ec6f378e5f76e8943a79865f5" + "sha2": "274eacb4eff7e5773666228a9546e9ab1ec68774" } ,{ "testCaseDescription": "javascript-while-statement-replacement-insert-test", @@ -38,7 +38,7 @@ "while-statement.js": [ { "span": { - "that": { + "insert": { "start": [ 1, 1 @@ -55,7 +55,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 1 @@ -77,9 +77,9 @@ "filePaths": [ "while-statement.js" ], - "sha1": "9704581566ea216ec6f378e5f76e8943a79865f5", + "sha1": "274eacb4eff7e5773666228a9546e9ab1ec68774", "gitDir": "test/corpus/repos/javascript", - "sha2": "fd7989e23defab92f730cb28cfdd04b4c9e2d31b" + "sha2": "1b77e40e3f6486158c79f7acc346e102d8a78007" } ,{ "testCaseDescription": "javascript-while-statement-delete-insert-test", @@ -88,7 +88,7 @@ "while-statement.js": [ { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -118,7 +118,7 @@ }, { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -153,9 +153,9 @@ "filePaths": [ "while-statement.js" ], - "sha1": "fd7989e23defab92f730cb28cfdd04b4c9e2d31b", + "sha1": "1b77e40e3f6486158c79f7acc346e102d8a78007", "gitDir": "test/corpus/repos/javascript", - "sha2": "9200999bd304f0dd206ad4fa0f6b52807b27b2b4" + "sha2": "0eafdfad1e7720c217b9395c5b16d0e449914dbe" } ,{ "testCaseDescription": "javascript-while-statement-replacement-test", @@ -164,7 +164,7 @@ "while-statement.js": [ { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -194,7 +194,7 @@ }, { "span": { - "these": [ + "replace": [ { "start": [ 1, @@ -229,9 +229,9 @@ "filePaths": [ "while-statement.js" ], - "sha1": "9200999bd304f0dd206ad4fa0f6b52807b27b2b4", + "sha1": "0eafdfad1e7720c217b9395c5b16d0e449914dbe", "gitDir": "test/corpus/repos/javascript", - "sha2": "2f2ca40848a11ece5334c303c012b3e46020fb7a" + "sha2": "31f8024c950f170297ffddb0f3d7b0b215c4e21f" } ,{ "testCaseDescription": "javascript-while-statement-delete-replacement-test", @@ -240,7 +240,7 @@ "while-statement.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -257,7 +257,7 @@ }, { "span": { - "this": { + "delete": { "start": [ 2, 1 @@ -274,7 +274,7 @@ }, { "span": { - "that": { + "insert": { "start": [ 2, 1 @@ -296,9 +296,9 @@ "filePaths": [ "while-statement.js" ], - "sha1": "2f2ca40848a11ece5334c303c012b3e46020fb7a", + "sha1": "31f8024c950f170297ffddb0f3d7b0b215c4e21f", "gitDir": "test/corpus/repos/javascript", - "sha2": "e048bb9d6a69bfd30b01c3ee83d5d28803dcfb57" + "sha2": "70bf5f2b28fde7bd03a50ad40833c344aec3f10a" } ,{ "testCaseDescription": "javascript-while-statement-delete-test", @@ -307,7 +307,7 @@ "while-statement.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -329,9 +329,9 @@ "filePaths": [ "while-statement.js" ], - "sha1": "e048bb9d6a69bfd30b01c3ee83d5d28803dcfb57", + "sha1": "70bf5f2b28fde7bd03a50ad40833c344aec3f10a", "gitDir": "test/corpus/repos/javascript", - "sha2": "1628b7a59734cf69c9965cadbe93776d2923085a" + "sha2": "2e362f8f0146680a3f4c3d5221130d532926b308" } ,{ "testCaseDescription": "javascript-while-statement-delete-rest-test", @@ -340,7 +340,7 @@ "while-statement.js": [ { "span": { - "this": { + "delete": { "start": [ 1, 1 @@ -362,7 +362,7 @@ "filePaths": [ "while-statement.js" ], - "sha1": "1628b7a59734cf69c9965cadbe93776d2923085a", + "sha1": "2e362f8f0146680a3f4c3d5221130d532926b308", "gitDir": "test/corpus/repos/javascript", - "sha2": "b9bce32850180705594c7350911bd0714243f188" + "sha2": "101c947313c24c2e76769c572c080adea44c80da" }] diff --git a/test/corpus/repos/javascript b/test/corpus/repos/javascript index f8683054b..f7d88a07b 160000 --- a/test/corpus/repos/javascript +++ b/test/corpus/repos/javascript @@ -1 +1 @@ -Subproject commit f8683054b3df6a44185993d0c11c1edcf4477b16 +Subproject commit f7d88a07b742fd7334d28806f01764ddfed94384 From 11d5cdcde73cbc5c2c22641b5b3f0e2b7d1bae6f Mon Sep 17 00:00:00 2001 From: joshvera Date: Tue, 11 Oct 2016 12:00:34 -0400 Subject: [PATCH 20/27] Bump tests --- .../javascript/anonymous-function.json | 28 +++++++++---------- .../anonymous-parameterless-function.json | 28 +++++++++---------- .../diff-summaries/javascript/array.json | 28 +++++++++---------- .../javascript/arrow-function.json | 28 +++++++++---------- .../diff-summaries/javascript/assignment.json | 28 +++++++++---------- .../javascript/bitwise-operator.json | 28 +++++++++---------- .../javascript/boolean-operator.json | 28 +++++++++---------- .../javascript/chained-callbacks.json | 28 +++++++++---------- .../javascript/chained-property-access.json | 28 +++++++++---------- .../diff-summaries/javascript/class.json | 28 +++++++++---------- .../javascript/comma-operator.json | 28 +++++++++---------- .../diff-summaries/javascript/comment.json | 28 +++++++++---------- .../javascript/constructor-call.json | 28 +++++++++---------- .../javascript/delete-operator.json | 28 +++++++++---------- .../javascript/do-while-statement.json | 28 +++++++++---------- .../diff-summaries/javascript/false.json | 28 +++++++++---------- .../javascript/for-in-statement.json | 28 +++++++++---------- .../for-loop-with-in-statement.json | 28 +++++++++---------- .../javascript/for-of-statement.json | 28 +++++++++---------- .../javascript/for-statement.json | 28 +++++++++---------- .../javascript/function-call-args.json | 28 +++++++++---------- .../javascript/function-call.json | 28 +++++++++---------- .../diff-summaries/javascript/function.json | 28 +++++++++---------- .../javascript/generator-function.json | 28 +++++++++---------- .../diff-summaries/javascript/identifier.json | 28 +++++++++---------- .../diff-summaries/javascript/if-else.json | 28 +++++++++---------- test/corpus/diff-summaries/javascript/if.json | 28 +++++++++---------- .../javascript/math-assignment-operator.json | 28 +++++++++---------- .../javascript/math-operator.json | 28 +++++++++---------- .../javascript/member-access-assignment.json | 28 +++++++++---------- .../javascript/member-access.json | 28 +++++++++---------- .../javascript/method-call.json | 28 +++++++++---------- .../javascript/named-function.json | 28 +++++++++---------- .../javascript/nested-functions.json | 28 +++++++++---------- .../diff-summaries/javascript/null.json | 28 +++++++++---------- .../diff-summaries/javascript/number.json | 28 +++++++++---------- .../javascript/object-with-methods.json | 28 +++++++++---------- .../diff-summaries/javascript/object.json | 28 +++++++++---------- .../diff-summaries/javascript/regex.json | 28 +++++++++---------- .../javascript/relational-operator.json | 28 +++++++++---------- .../javascript/return-statement.json | 28 +++++++++---------- .../diff-summaries/javascript/string.json | 28 +++++++++---------- .../subscript-access-assignment.json | 28 +++++++++---------- .../javascript/subscript-access-string.json | 28 +++++++++---------- .../javascript/subscript-access-variable.json | 28 +++++++++---------- .../javascript/switch-statement.json | 28 +++++++++---------- .../javascript/template-string.json | 28 +++++++++---------- .../diff-summaries/javascript/ternary.json | 28 +++++++++---------- .../javascript/this-expression.json | 28 +++++++++---------- .../javascript/throw-statement.json | 28 +++++++++---------- .../diff-summaries/javascript/true.json | 28 +++++++++---------- .../javascript/try-statement.json | 28 +++++++++---------- .../javascript/type-operator.json | 28 +++++++++---------- .../diff-summaries/javascript/undefined.json | 28 +++++++++---------- .../javascript/var-declaration.json | 28 +++++++++---------- .../diff-summaries/javascript/variable.json | 28 +++++++++---------- .../javascript/void-operator.json | 28 +++++++++---------- .../javascript/while-statement.json | 28 +++++++++---------- test/corpus/repos/javascript | 2 +- 59 files changed, 813 insertions(+), 813 deletions(-) diff --git a/test/corpus/diff-summaries/javascript/anonymous-function.json b/test/corpus/diff-summaries/javascript/anonymous-function.json index 71d3aaff7..c2d795c01 100644 --- a/test/corpus/diff-summaries/javascript/anonymous-function.json +++ b/test/corpus/diff-summaries/javascript/anonymous-function.json @@ -27,9 +27,9 @@ "filePaths": [ "anonymous-function.js" ], - "sha1": "b4b200a6398403b141e5fd87506899af661b97a6", + "sha1": "804f2056b155a51e98aacc2af9f2950bab4cbaf8", "gitDir": "test/corpus/repos/javascript", - "sha2": "8a39270e274dfce45be0134070ed337077a22812" + "sha2": "eda4f0da16edab81e68fa4bd40bdf68317bf4a75" } ,{ "testCaseDescription": "javascript-anonymous-function-replacement-insert-test", @@ -77,9 +77,9 @@ "filePaths": [ "anonymous-function.js" ], - "sha1": "8a39270e274dfce45be0134070ed337077a22812", + "sha1": "eda4f0da16edab81e68fa4bd40bdf68317bf4a75", "gitDir": "test/corpus/repos/javascript", - "sha2": "0d7f05ae9912519348e739c2dd350509ece5bfd6" + "sha2": "319f65e34cfba43aa61e6e58594d3e4cb4d21be2" } ,{ "testCaseDescription": "javascript-anonymous-function-delete-insert-test", @@ -213,9 +213,9 @@ "filePaths": [ "anonymous-function.js" ], - "sha1": "0d7f05ae9912519348e739c2dd350509ece5bfd6", + "sha1": "319f65e34cfba43aa61e6e58594d3e4cb4d21be2", "gitDir": "test/corpus/repos/javascript", - "sha2": "f0269043db13f7333a5f2633fc30ff94c7321846" + "sha2": "ca9fb83ac14937adeac12170c6faf20798086a2c" } ,{ "testCaseDescription": "javascript-anonymous-function-replacement-test", @@ -349,9 +349,9 @@ "filePaths": [ "anonymous-function.js" ], - "sha1": "f0269043db13f7333a5f2633fc30ff94c7321846", + "sha1": "ca9fb83ac14937adeac12170c6faf20798086a2c", "gitDir": "test/corpus/repos/javascript", - "sha2": "3d445ebd82f990df87119eb1b00223e23be72ec5" + "sha2": "3dc91ac24280fa629998c616530cd3310d6955a6" } ,{ "testCaseDescription": "javascript-anonymous-function-delete-replacement-test", @@ -416,9 +416,9 @@ "filePaths": [ "anonymous-function.js" ], - "sha1": "3d445ebd82f990df87119eb1b00223e23be72ec5", + "sha1": "3dc91ac24280fa629998c616530cd3310d6955a6", "gitDir": "test/corpus/repos/javascript", - "sha2": "25bca4ac08d3f6ffba5acbecfe0cd7172d466cfe" + "sha2": "9751610debe4f24e742ec7ffa6abe965144c8345" } ,{ "testCaseDescription": "javascript-anonymous-function-delete-test", @@ -449,9 +449,9 @@ "filePaths": [ "anonymous-function.js" ], - "sha1": "25bca4ac08d3f6ffba5acbecfe0cd7172d466cfe", + "sha1": "9751610debe4f24e742ec7ffa6abe965144c8345", "gitDir": "test/corpus/repos/javascript", - "sha2": "39a82d9ad7a0b2894c3c2be17a141e2ee5ff886c" + "sha2": "962e9daa6bd0b7ec868e454f11d5aa3b6b1c4424" } ,{ "testCaseDescription": "javascript-anonymous-function-delete-rest-test", @@ -482,7 +482,7 @@ "filePaths": [ "anonymous-function.js" ], - "sha1": "39a82d9ad7a0b2894c3c2be17a141e2ee5ff886c", + "sha1": "962e9daa6bd0b7ec868e454f11d5aa3b6b1c4424", "gitDir": "test/corpus/repos/javascript", - "sha2": "ab4f48bf9115a296943ba7b2304e674c7149c29d" + "sha2": "7a7a8f4f58f05a4dcfb46eb314604dfd141d6d2c" }] diff --git a/test/corpus/diff-summaries/javascript/anonymous-parameterless-function.json b/test/corpus/diff-summaries/javascript/anonymous-parameterless-function.json index 495812b5a..d7918307f 100644 --- a/test/corpus/diff-summaries/javascript/anonymous-parameterless-function.json +++ b/test/corpus/diff-summaries/javascript/anonymous-parameterless-function.json @@ -27,9 +27,9 @@ "filePaths": [ "anonymous-parameterless-function.js" ], - "sha1": "ab4f48bf9115a296943ba7b2304e674c7149c29d", + "sha1": "7a7a8f4f58f05a4dcfb46eb314604dfd141d6d2c", "gitDir": "test/corpus/repos/javascript", - "sha2": "f43074bc2b6753a364b3b13cfc58818b23757002" + "sha2": "d42d2dbcaf69d5ac4a623c4857f1654275987a45" } ,{ "testCaseDescription": "javascript-anonymous-parameterless-function-replacement-insert-test", @@ -77,9 +77,9 @@ "filePaths": [ "anonymous-parameterless-function.js" ], - "sha1": "f43074bc2b6753a364b3b13cfc58818b23757002", + "sha1": "d42d2dbcaf69d5ac4a623c4857f1654275987a45", "gitDir": "test/corpus/repos/javascript", - "sha2": "26e0b2b93bae701963cdefbc3a8c5398186e19e5" + "sha2": "064b910da3162d2be95198714ff8eeb6057b1cab" } ,{ "testCaseDescription": "javascript-anonymous-parameterless-function-delete-insert-test", @@ -123,9 +123,9 @@ "filePaths": [ "anonymous-parameterless-function.js" ], - "sha1": "26e0b2b93bae701963cdefbc3a8c5398186e19e5", + "sha1": "064b910da3162d2be95198714ff8eeb6057b1cab", "gitDir": "test/corpus/repos/javascript", - "sha2": "fd8dd926a95d09f8bc5ddd70f6332f70811861bd" + "sha2": "900df08eb69e5ec7cf0935f834dff84d2a8f938d" } ,{ "testCaseDescription": "javascript-anonymous-parameterless-function-replacement-test", @@ -169,9 +169,9 @@ "filePaths": [ "anonymous-parameterless-function.js" ], - "sha1": "fd8dd926a95d09f8bc5ddd70f6332f70811861bd", + "sha1": "900df08eb69e5ec7cf0935f834dff84d2a8f938d", "gitDir": "test/corpus/repos/javascript", - "sha2": "e4cf93ae56fcf34133d7e449d6d32d543f47a39e" + "sha2": "0dee59c204e74e8e797b0acf9295c5c13b3be400" } ,{ "testCaseDescription": "javascript-anonymous-parameterless-function-delete-replacement-test", @@ -236,9 +236,9 @@ "filePaths": [ "anonymous-parameterless-function.js" ], - "sha1": "e4cf93ae56fcf34133d7e449d6d32d543f47a39e", + "sha1": "0dee59c204e74e8e797b0acf9295c5c13b3be400", "gitDir": "test/corpus/repos/javascript", - "sha2": "91f3b9d0e7f9a84e72e0d8d85f9ae10e65ab5c75" + "sha2": "afd1bced812dcd0391498cd66d5392edeb3a6857" } ,{ "testCaseDescription": "javascript-anonymous-parameterless-function-delete-test", @@ -269,9 +269,9 @@ "filePaths": [ "anonymous-parameterless-function.js" ], - "sha1": "91f3b9d0e7f9a84e72e0d8d85f9ae10e65ab5c75", + "sha1": "afd1bced812dcd0391498cd66d5392edeb3a6857", "gitDir": "test/corpus/repos/javascript", - "sha2": "17288c5650b4e44ed2b59fa8b3832f99c88af33c" + "sha2": "088434491f81994ef21a56a8e814f4c82af996b2" } ,{ "testCaseDescription": "javascript-anonymous-parameterless-function-delete-rest-test", @@ -302,7 +302,7 @@ "filePaths": [ "anonymous-parameterless-function.js" ], - "sha1": "17288c5650b4e44ed2b59fa8b3832f99c88af33c", + "sha1": "088434491f81994ef21a56a8e814f4c82af996b2", "gitDir": "test/corpus/repos/javascript", - "sha2": "613f8b8ea74085ab35b7398fe3f636eda7d63fa2" + "sha2": "2a302d002490d7bb5aff372747a028cec52c1b4b" }] diff --git a/test/corpus/diff-summaries/javascript/array.json b/test/corpus/diff-summaries/javascript/array.json index 23f9e0773..f2c4336a7 100644 --- a/test/corpus/diff-summaries/javascript/array.json +++ b/test/corpus/diff-summaries/javascript/array.json @@ -27,9 +27,9 @@ "filePaths": [ "array.js" ], - "sha1": "54c26c85b1720507e7c076553120465986fd2894", + "sha1": "04b681e1190310f6148595f3d80260ae13299d43", "gitDir": "test/corpus/repos/javascript", - "sha2": "f5bb66df169bf045026ba4442a4d974847db3489" + "sha2": "f764a79ec733a7f8fd0cb4016f918b2eefa89b51" } ,{ "testCaseDescription": "javascript-array-replacement-insert-test", @@ -77,9 +77,9 @@ "filePaths": [ "array.js" ], - "sha1": "f5bb66df169bf045026ba4442a4d974847db3489", + "sha1": "f764a79ec733a7f8fd0cb4016f918b2eefa89b51", "gitDir": "test/corpus/repos/javascript", - "sha2": "0cadc95617a4d5b8ed257445b10f7a78fcf7cf64" + "sha2": "5a2f8c9043ef76d04634f22dd120f3c950711887" } ,{ "testCaseDescription": "javascript-array-delete-insert-test", @@ -110,9 +110,9 @@ "filePaths": [ "array.js" ], - "sha1": "0cadc95617a4d5b8ed257445b10f7a78fcf7cf64", + "sha1": "5a2f8c9043ef76d04634f22dd120f3c950711887", "gitDir": "test/corpus/repos/javascript", - "sha2": "5e1cd2633508c891278e8107d436c8a5814c476d" + "sha2": "5c1725c772ad618a734f78ba80bc29990a06f8a1" } ,{ "testCaseDescription": "javascript-array-replacement-test", @@ -143,9 +143,9 @@ "filePaths": [ "array.js" ], - "sha1": "5e1cd2633508c891278e8107d436c8a5814c476d", + "sha1": "5c1725c772ad618a734f78ba80bc29990a06f8a1", "gitDir": "test/corpus/repos/javascript", - "sha2": "5dfefcf9ca75459d4f86e85cfb73f1f538770740" + "sha2": "779013762c7bcb016f2ec80ab3caed4384fc4113" } ,{ "testCaseDescription": "javascript-array-delete-replacement-test", @@ -210,9 +210,9 @@ "filePaths": [ "array.js" ], - "sha1": "5dfefcf9ca75459d4f86e85cfb73f1f538770740", + "sha1": "779013762c7bcb016f2ec80ab3caed4384fc4113", "gitDir": "test/corpus/repos/javascript", - "sha2": "b8ede0fa6f522240174653fec41a06d409230f4c" + "sha2": "daf668c7bbccb5e2a70cd5e6d081ea35dfddb879" } ,{ "testCaseDescription": "javascript-array-delete-test", @@ -243,9 +243,9 @@ "filePaths": [ "array.js" ], - "sha1": "b8ede0fa6f522240174653fec41a06d409230f4c", + "sha1": "daf668c7bbccb5e2a70cd5e6d081ea35dfddb879", "gitDir": "test/corpus/repos/javascript", - "sha2": "cdccd002f81bf773a827a1be1f2c1740ac6c5606" + "sha2": "6e471401fdfac17a93fa8e5fb87924864dd4b07b" } ,{ "testCaseDescription": "javascript-array-delete-rest-test", @@ -276,7 +276,7 @@ "filePaths": [ "array.js" ], - "sha1": "cdccd002f81bf773a827a1be1f2c1740ac6c5606", + "sha1": "6e471401fdfac17a93fa8e5fb87924864dd4b07b", "gitDir": "test/corpus/repos/javascript", - "sha2": "294584bae27cd565886c9c1064c423ab7a04e42d" + "sha2": "0921c7be9afb30bdf6fa3861d12c20a87ae67736" }] diff --git a/test/corpus/diff-summaries/javascript/arrow-function.json b/test/corpus/diff-summaries/javascript/arrow-function.json index d65aded44..220d8100d 100644 --- a/test/corpus/diff-summaries/javascript/arrow-function.json +++ b/test/corpus/diff-summaries/javascript/arrow-function.json @@ -27,9 +27,9 @@ "filePaths": [ "arrow-function.js" ], - "sha1": "822aeb40bb7867ac30402c6f1af8dcea662ed4fb", + "sha1": "2327a0433e3123ddf19226ee5172c928f24b3af1", "gitDir": "test/corpus/repos/javascript", - "sha2": "65025ba223fc1045c1271288840a1eca67fe0c6d" + "sha2": "fb18e7576ad5e8c1f6007ec75e366d78c401fcc8" } ,{ "testCaseDescription": "javascript-arrow-function-replacement-insert-test", @@ -77,9 +77,9 @@ "filePaths": [ "arrow-function.js" ], - "sha1": "65025ba223fc1045c1271288840a1eca67fe0c6d", + "sha1": "fb18e7576ad5e8c1f6007ec75e366d78c401fcc8", "gitDir": "test/corpus/repos/javascript", - "sha2": "c10fa6691cf995ebcc6d84b4ab6522f4ccfe28c1" + "sha2": "140eb10dce63b1e9b8edd202efdf5ede1cfee31f" } ,{ "testCaseDescription": "javascript-arrow-function-delete-insert-test", @@ -123,9 +123,9 @@ "filePaths": [ "arrow-function.js" ], - "sha1": "c10fa6691cf995ebcc6d84b4ab6522f4ccfe28c1", + "sha1": "140eb10dce63b1e9b8edd202efdf5ede1cfee31f", "gitDir": "test/corpus/repos/javascript", - "sha2": "a2267c8a6ed335962c12381cea182a78263e3a03" + "sha2": "38800991dd39be51410c9a4cd97f0b5ca90ec95d" } ,{ "testCaseDescription": "javascript-arrow-function-replacement-test", @@ -169,9 +169,9 @@ "filePaths": [ "arrow-function.js" ], - "sha1": "a2267c8a6ed335962c12381cea182a78263e3a03", + "sha1": "38800991dd39be51410c9a4cd97f0b5ca90ec95d", "gitDir": "test/corpus/repos/javascript", - "sha2": "9e4a66eeb46e9a280a6f8efe417f600948b11100" + "sha2": "cda2aefb00dc0c425737770e5d0f71d2952dc41c" } ,{ "testCaseDescription": "javascript-arrow-function-delete-replacement-test", @@ -236,9 +236,9 @@ "filePaths": [ "arrow-function.js" ], - "sha1": "9e4a66eeb46e9a280a6f8efe417f600948b11100", + "sha1": "cda2aefb00dc0c425737770e5d0f71d2952dc41c", "gitDir": "test/corpus/repos/javascript", - "sha2": "91749e540ce622a0f38a4d2beb333b0287429c03" + "sha2": "09183e7e67ff885a3eb4d9cc48700496f93274c6" } ,{ "testCaseDescription": "javascript-arrow-function-delete-test", @@ -269,9 +269,9 @@ "filePaths": [ "arrow-function.js" ], - "sha1": "91749e540ce622a0f38a4d2beb333b0287429c03", + "sha1": "09183e7e67ff885a3eb4d9cc48700496f93274c6", "gitDir": "test/corpus/repos/javascript", - "sha2": "30c18032df971c15b87ba03124262c4a17d80aa3" + "sha2": "a36d1e0f9a73f7a5f4fff31fb53773484b26f1b3" } ,{ "testCaseDescription": "javascript-arrow-function-delete-rest-test", @@ -302,7 +302,7 @@ "filePaths": [ "arrow-function.js" ], - "sha1": "30c18032df971c15b87ba03124262c4a17d80aa3", + "sha1": "a36d1e0f9a73f7a5f4fff31fb53773484b26f1b3", "gitDir": "test/corpus/repos/javascript", - "sha2": "016ccc9573eb5bfe5ec52dcd5bb58239755ca8fd" + "sha2": "dcaa57653ecd13d885de551a47032d37ef10e47e" }] diff --git a/test/corpus/diff-summaries/javascript/assignment.json b/test/corpus/diff-summaries/javascript/assignment.json index f3875821a..f20474fab 100644 --- a/test/corpus/diff-summaries/javascript/assignment.json +++ b/test/corpus/diff-summaries/javascript/assignment.json @@ -27,9 +27,9 @@ "filePaths": [ "assignment.js" ], - "sha1": "5c8734b51a5ad1b14629d6ba40597bcb713ffab0", + "sha1": "7c328351e5e8debb38b46a45f43481581e438666", "gitDir": "test/corpus/repos/javascript", - "sha2": "337b7362f5cac47c55723909e65a5f6be893fb56" + "sha2": "6ba03898f9fd18c886831a602180fad0fc468e31" } ,{ "testCaseDescription": "javascript-assignment-replacement-insert-test", @@ -77,9 +77,9 @@ "filePaths": [ "assignment.js" ], - "sha1": "337b7362f5cac47c55723909e65a5f6be893fb56", + "sha1": "6ba03898f9fd18c886831a602180fad0fc468e31", "gitDir": "test/corpus/repos/javascript", - "sha2": "f7ec281cb1fd5eed4e82f0c012db2b5dfcb6ab05" + "sha2": "f70ee402927b75eeae9a6d38d4da7c130dda80e0" } ,{ "testCaseDescription": "javascript-assignment-delete-insert-test", @@ -123,9 +123,9 @@ "filePaths": [ "assignment.js" ], - "sha1": "f7ec281cb1fd5eed4e82f0c012db2b5dfcb6ab05", + "sha1": "f70ee402927b75eeae9a6d38d4da7c130dda80e0", "gitDir": "test/corpus/repos/javascript", - "sha2": "20ba6de9efb5238ddd88277e6ff00352cc51480c" + "sha2": "98be0baf2ee4ad6d59621872395016241d9dd66e" } ,{ "testCaseDescription": "javascript-assignment-replacement-test", @@ -169,9 +169,9 @@ "filePaths": [ "assignment.js" ], - "sha1": "20ba6de9efb5238ddd88277e6ff00352cc51480c", + "sha1": "98be0baf2ee4ad6d59621872395016241d9dd66e", "gitDir": "test/corpus/repos/javascript", - "sha2": "67e1be509cad5719465e7c5735d0fade6cd9b571" + "sha2": "53d0889371bf94bcfac80d7650321255b41eeb38" } ,{ "testCaseDescription": "javascript-assignment-delete-replacement-test", @@ -236,9 +236,9 @@ "filePaths": [ "assignment.js" ], - "sha1": "67e1be509cad5719465e7c5735d0fade6cd9b571", + "sha1": "53d0889371bf94bcfac80d7650321255b41eeb38", "gitDir": "test/corpus/repos/javascript", - "sha2": "faacec7eb75d0f64116bcd8aae7eee87a10b820b" + "sha2": "f1f84edf5d0d233cb48a55774f0ee44cdb8143f6" } ,{ "testCaseDescription": "javascript-assignment-delete-test", @@ -269,9 +269,9 @@ "filePaths": [ "assignment.js" ], - "sha1": "faacec7eb75d0f64116bcd8aae7eee87a10b820b", + "sha1": "f1f84edf5d0d233cb48a55774f0ee44cdb8143f6", "gitDir": "test/corpus/repos/javascript", - "sha2": "cae8e1f9eb998f4bab6d091392b36dd4282c5a09" + "sha2": "358d66dc46c668b9e484e97231882e45e366d03f" } ,{ "testCaseDescription": "javascript-assignment-delete-rest-test", @@ -302,7 +302,7 @@ "filePaths": [ "assignment.js" ], - "sha1": "cae8e1f9eb998f4bab6d091392b36dd4282c5a09", + "sha1": "358d66dc46c668b9e484e97231882e45e366d03f", "gitDir": "test/corpus/repos/javascript", - "sha2": "5abf5273d87f2dd381fecb3cb1da4b3205c43884" + "sha2": "a4003ba4e78b0ae460decba084c34b15da1aa05e" }] diff --git a/test/corpus/diff-summaries/javascript/bitwise-operator.json b/test/corpus/diff-summaries/javascript/bitwise-operator.json index 6b55766a6..d9477385f 100644 --- a/test/corpus/diff-summaries/javascript/bitwise-operator.json +++ b/test/corpus/diff-summaries/javascript/bitwise-operator.json @@ -27,9 +27,9 @@ "filePaths": [ "bitwise-operator.js" ], - "sha1": "0a55bedb688b2d873dec7f8d898dcf6a7343e8bc", + "sha1": "8a735ff7a31a77424b93ff74548a5ca81e1dba3f", "gitDir": "test/corpus/repos/javascript", - "sha2": "c9e68c8a09b1d6620d90edffc20264f84e760aad" + "sha2": "4e79490e2d815ab0f81dd5cec2022bf83f3ed235" } ,{ "testCaseDescription": "javascript-bitwise-operator-replacement-insert-test", @@ -77,9 +77,9 @@ "filePaths": [ "bitwise-operator.js" ], - "sha1": "c9e68c8a09b1d6620d90edffc20264f84e760aad", + "sha1": "4e79490e2d815ab0f81dd5cec2022bf83f3ed235", "gitDir": "test/corpus/repos/javascript", - "sha2": "790495da1abb04f294dbbcb0e6d94b8f7d8ff728" + "sha2": "72d4748300623514be5fd407a75cff6b3378b955" } ,{ "testCaseDescription": "javascript-bitwise-operator-delete-insert-test", @@ -123,9 +123,9 @@ "filePaths": [ "bitwise-operator.js" ], - "sha1": "790495da1abb04f294dbbcb0e6d94b8f7d8ff728", + "sha1": "72d4748300623514be5fd407a75cff6b3378b955", "gitDir": "test/corpus/repos/javascript", - "sha2": "195279d699cd8d5687b464de6cf9e73e9669d9bb" + "sha2": "69b73f68b68e2ab525a929d74e3a43df64ef88b4" } ,{ "testCaseDescription": "javascript-bitwise-operator-replacement-test", @@ -169,9 +169,9 @@ "filePaths": [ "bitwise-operator.js" ], - "sha1": "195279d699cd8d5687b464de6cf9e73e9669d9bb", + "sha1": "69b73f68b68e2ab525a929d74e3a43df64ef88b4", "gitDir": "test/corpus/repos/javascript", - "sha2": "741ea0e0bfe434fb44bb43fcddec0d57c1715cd8" + "sha2": "c12333aa2b749340791848b0f57610a5c6b52faf" } ,{ "testCaseDescription": "javascript-bitwise-operator-delete-replacement-test", @@ -236,9 +236,9 @@ "filePaths": [ "bitwise-operator.js" ], - "sha1": "741ea0e0bfe434fb44bb43fcddec0d57c1715cd8", + "sha1": "c12333aa2b749340791848b0f57610a5c6b52faf", "gitDir": "test/corpus/repos/javascript", - "sha2": "4cfd45eae2864683d531ee98115336efb4df42ba" + "sha2": "1e669bdb2a1cd74b9f08dd9b1aa43014973a1f8c" } ,{ "testCaseDescription": "javascript-bitwise-operator-delete-test", @@ -269,9 +269,9 @@ "filePaths": [ "bitwise-operator.js" ], - "sha1": "4cfd45eae2864683d531ee98115336efb4df42ba", + "sha1": "1e669bdb2a1cd74b9f08dd9b1aa43014973a1f8c", "gitDir": "test/corpus/repos/javascript", - "sha2": "07651054734923312e1f86568b4c74588c020878" + "sha2": "ac8d1c7f04041084bdee5e5d66b09735976372c2" } ,{ "testCaseDescription": "javascript-bitwise-operator-delete-rest-test", @@ -302,7 +302,7 @@ "filePaths": [ "bitwise-operator.js" ], - "sha1": "07651054734923312e1f86568b4c74588c020878", + "sha1": "ac8d1c7f04041084bdee5e5d66b09735976372c2", "gitDir": "test/corpus/repos/javascript", - "sha2": "44726d92bc92a8541b8e3089ee22826fa31cdc69" + "sha2": "088c27d2d4e2150bac4bff85c129df8d90a407c2" }] diff --git a/test/corpus/diff-summaries/javascript/boolean-operator.json b/test/corpus/diff-summaries/javascript/boolean-operator.json index 911c1d0a7..bd975a9c8 100644 --- a/test/corpus/diff-summaries/javascript/boolean-operator.json +++ b/test/corpus/diff-summaries/javascript/boolean-operator.json @@ -27,9 +27,9 @@ "filePaths": [ "boolean-operator.js" ], - "sha1": "7e1caa9a941a609d09c734937d05d7b2414e8219", + "sha1": "4a00f98e1f34850ca8d14b8f33de4f8a0fcb7c40", "gitDir": "test/corpus/repos/javascript", - "sha2": "c0e2708f57e17a4ce2c1696e880ed30bad18ca26" + "sha2": "95d128540dedb5ebcc33abd84e10116e0fd05c50" } ,{ "testCaseDescription": "javascript-boolean-operator-replacement-insert-test", @@ -77,9 +77,9 @@ "filePaths": [ "boolean-operator.js" ], - "sha1": "c0e2708f57e17a4ce2c1696e880ed30bad18ca26", + "sha1": "95d128540dedb5ebcc33abd84e10116e0fd05c50", "gitDir": "test/corpus/repos/javascript", - "sha2": "0e87089f205a053aaba445030d07334a2f0a3c0d" + "sha2": "ae35cc9ea4ccbcaf06b7156b11ca36fb217b50da" } ,{ "testCaseDescription": "javascript-boolean-operator-delete-insert-test", @@ -90,9 +90,9 @@ "filePaths": [ "boolean-operator.js" ], - "sha1": "0e87089f205a053aaba445030d07334a2f0a3c0d", + "sha1": "ae35cc9ea4ccbcaf06b7156b11ca36fb217b50da", "gitDir": "test/corpus/repos/javascript", - "sha2": "0e77f8929e9863a8750c2c783e827153e0f09ed5" + "sha2": "44bf52b057f77b274462a57449b1a91efaa6b206" } ,{ "testCaseDescription": "javascript-boolean-operator-replacement-test", @@ -103,9 +103,9 @@ "filePaths": [ "boolean-operator.js" ], - "sha1": "0e77f8929e9863a8750c2c783e827153e0f09ed5", + "sha1": "44bf52b057f77b274462a57449b1a91efaa6b206", "gitDir": "test/corpus/repos/javascript", - "sha2": "7eb85e05ccbfe6f171137c8e5e0bd9574e4089f6" + "sha2": "045f496374fb481d0b8ffdd5792f8ee519eb8389" } ,{ "testCaseDescription": "javascript-boolean-operator-delete-replacement-test", @@ -136,9 +136,9 @@ "filePaths": [ "boolean-operator.js" ], - "sha1": "7eb85e05ccbfe6f171137c8e5e0bd9574e4089f6", + "sha1": "045f496374fb481d0b8ffdd5792f8ee519eb8389", "gitDir": "test/corpus/repos/javascript", - "sha2": "2c2f7fe0801ea179c43b3b4f8cdd228c792c7b79" + "sha2": "abe63da8bfcb6f56c48ae2cefc32dffb8707b534" } ,{ "testCaseDescription": "javascript-boolean-operator-delete-test", @@ -169,9 +169,9 @@ "filePaths": [ "boolean-operator.js" ], - "sha1": "2c2f7fe0801ea179c43b3b4f8cdd228c792c7b79", + "sha1": "abe63da8bfcb6f56c48ae2cefc32dffb8707b534", "gitDir": "test/corpus/repos/javascript", - "sha2": "868176abe9d7d38af9fa93baea780e56ecbedb28" + "sha2": "30cb690c861b4c9f1c92857e4098043dd7165fa1" } ,{ "testCaseDescription": "javascript-boolean-operator-delete-rest-test", @@ -202,7 +202,7 @@ "filePaths": [ "boolean-operator.js" ], - "sha1": "868176abe9d7d38af9fa93baea780e56ecbedb28", + "sha1": "30cb690c861b4c9f1c92857e4098043dd7165fa1", "gitDir": "test/corpus/repos/javascript", - "sha2": "0a55bedb688b2d873dec7f8d898dcf6a7343e8bc" + "sha2": "8a735ff7a31a77424b93ff74548a5ca81e1dba3f" }] diff --git a/test/corpus/diff-summaries/javascript/chained-callbacks.json b/test/corpus/diff-summaries/javascript/chained-callbacks.json index ce6891a72..eb5f48219 100644 --- a/test/corpus/diff-summaries/javascript/chained-callbacks.json +++ b/test/corpus/diff-summaries/javascript/chained-callbacks.json @@ -27,9 +27,9 @@ "filePaths": [ "chained-callbacks.js" ], - "sha1": "0a38cbb0dc46ccdf6a85eb82cfd1702afb266bac", + "sha1": "20bc26cc8af9efd835b023b026250f920bf1cc88", "gitDir": "test/corpus/repos/javascript", - "sha2": "f17c7e647d17c88e76157f48d58a43710d9f8d15" + "sha2": "8c05a8c012b065745a2da67a5a6e1bce328fd6b6" } ,{ "testCaseDescription": "javascript-chained-callbacks-replacement-insert-test", @@ -77,9 +77,9 @@ "filePaths": [ "chained-callbacks.js" ], - "sha1": "f17c7e647d17c88e76157f48d58a43710d9f8d15", + "sha1": "8c05a8c012b065745a2da67a5a6e1bce328fd6b6", "gitDir": "test/corpus/repos/javascript", - "sha2": "df48ea9931d0b7596f69131680320c73080026d1" + "sha2": "6869215944dfc529db1c0e731d0640f9a85d1040" } ,{ "testCaseDescription": "javascript-chained-callbacks-delete-insert-test", @@ -183,9 +183,9 @@ "filePaths": [ "chained-callbacks.js" ], - "sha1": "df48ea9931d0b7596f69131680320c73080026d1", + "sha1": "6869215944dfc529db1c0e731d0640f9a85d1040", "gitDir": "test/corpus/repos/javascript", - "sha2": "27bac95cea0012c651e3ce2a835a4d8720bad48b" + "sha2": "4c964599e2c3f646a49bd3c5a0ad7f28bb4e76f8" } ,{ "testCaseDescription": "javascript-chained-callbacks-replacement-test", @@ -289,9 +289,9 @@ "filePaths": [ "chained-callbacks.js" ], - "sha1": "27bac95cea0012c651e3ce2a835a4d8720bad48b", + "sha1": "4c964599e2c3f646a49bd3c5a0ad7f28bb4e76f8", "gitDir": "test/corpus/repos/javascript", - "sha2": "9cea77c1d3d51605b53ac00289cee931ea1a2359" + "sha2": "20c8a9a737d91e365f686ac9ef3ea3ece6bcf5ed" } ,{ "testCaseDescription": "javascript-chained-callbacks-delete-replacement-test", @@ -356,9 +356,9 @@ "filePaths": [ "chained-callbacks.js" ], - "sha1": "9cea77c1d3d51605b53ac00289cee931ea1a2359", + "sha1": "20c8a9a737d91e365f686ac9ef3ea3ece6bcf5ed", "gitDir": "test/corpus/repos/javascript", - "sha2": "c8f10bef923b07232331fa6453bf098ed1ffbe0f" + "sha2": "883ffc29d09b541a5c4d9e4674d5c04f876a40a2" } ,{ "testCaseDescription": "javascript-chained-callbacks-delete-test", @@ -389,9 +389,9 @@ "filePaths": [ "chained-callbacks.js" ], - "sha1": "c8f10bef923b07232331fa6453bf098ed1ffbe0f", + "sha1": "883ffc29d09b541a5c4d9e4674d5c04f876a40a2", "gitDir": "test/corpus/repos/javascript", - "sha2": "7060c31a4c8985ec7bea937ac90a427fee943955" + "sha2": "76d7d961c5ea2ade3fdd136a056c683732a81a25" } ,{ "testCaseDescription": "javascript-chained-callbacks-delete-rest-test", @@ -422,7 +422,7 @@ "filePaths": [ "chained-callbacks.js" ], - "sha1": "7060c31a4c8985ec7bea937ac90a427fee943955", + "sha1": "76d7d961c5ea2ade3fdd136a056c683732a81a25", "gitDir": "test/corpus/repos/javascript", - "sha2": "69d03ecd07566e6fa325c378815462768d32a996" + "sha2": "bd29fccbe38961789cd724a6537993e68f491091" }] diff --git a/test/corpus/diff-summaries/javascript/chained-property-access.json b/test/corpus/diff-summaries/javascript/chained-property-access.json index 1c3da7126..3ba8b8003 100644 --- a/test/corpus/diff-summaries/javascript/chained-property-access.json +++ b/test/corpus/diff-summaries/javascript/chained-property-access.json @@ -27,9 +27,9 @@ "filePaths": [ "chained-property-access.js" ], - "sha1": "41bf287dfe63a1096787b4f7409a469d078c25b7", + "sha1": "9dc1c8722d84e3f245688e90b8cf7155c95f446f", "gitDir": "test/corpus/repos/javascript", - "sha2": "bb2e9e006cd25f6252a12922b0818df7ec356ec6" + "sha2": "8afef92d997e837342429dbbacb19365f39eb7b4" } ,{ "testCaseDescription": "javascript-chained-property-access-replacement-insert-test", @@ -77,9 +77,9 @@ "filePaths": [ "chained-property-access.js" ], - "sha1": "bb2e9e006cd25f6252a12922b0818df7ec356ec6", + "sha1": "8afef92d997e837342429dbbacb19365f39eb7b4", "gitDir": "test/corpus/repos/javascript", - "sha2": "31fbee39c50df203b0073b27882592050176fa9f" + "sha2": "4475e0d7eb0e590853f495dd1db81601b6bc9dd3" } ,{ "testCaseDescription": "javascript-chained-property-access-delete-insert-test", @@ -153,9 +153,9 @@ "filePaths": [ "chained-property-access.js" ], - "sha1": "31fbee39c50df203b0073b27882592050176fa9f", + "sha1": "4475e0d7eb0e590853f495dd1db81601b6bc9dd3", "gitDir": "test/corpus/repos/javascript", - "sha2": "72a5d1937c1b757cb84f78854fd3c47f3eced7f3" + "sha2": "030352703839b25bbdacac36ddeabb1a831ad05a" } ,{ "testCaseDescription": "javascript-chained-property-access-replacement-test", @@ -229,9 +229,9 @@ "filePaths": [ "chained-property-access.js" ], - "sha1": "72a5d1937c1b757cb84f78854fd3c47f3eced7f3", + "sha1": "030352703839b25bbdacac36ddeabb1a831ad05a", "gitDir": "test/corpus/repos/javascript", - "sha2": "0ce34c376e1ce69ad7f72639e51fb3a2c0e0c182" + "sha2": "59dd2644428d0c34aa9181e402e1bb4e823ea8de" } ,{ "testCaseDescription": "javascript-chained-property-access-delete-replacement-test", @@ -296,9 +296,9 @@ "filePaths": [ "chained-property-access.js" ], - "sha1": "0ce34c376e1ce69ad7f72639e51fb3a2c0e0c182", + "sha1": "59dd2644428d0c34aa9181e402e1bb4e823ea8de", "gitDir": "test/corpus/repos/javascript", - "sha2": "5a32624882255d98a4708e2cf87c30a64b405b4f" + "sha2": "bad1b125972f03fd282dbf26f9adfa1315031ca7" } ,{ "testCaseDescription": "javascript-chained-property-access-delete-test", @@ -329,9 +329,9 @@ "filePaths": [ "chained-property-access.js" ], - "sha1": "5a32624882255d98a4708e2cf87c30a64b405b4f", + "sha1": "bad1b125972f03fd282dbf26f9adfa1315031ca7", "gitDir": "test/corpus/repos/javascript", - "sha2": "0902995588a5793f287b8aab2a3657a6ec1fbcdc" + "sha2": "cf0b7cc3662ba96a6efe6d01c4baf13e04e1a789" } ,{ "testCaseDescription": "javascript-chained-property-access-delete-rest-test", @@ -362,7 +362,7 @@ "filePaths": [ "chained-property-access.js" ], - "sha1": "0902995588a5793f287b8aab2a3657a6ec1fbcdc", + "sha1": "cf0b7cc3662ba96a6efe6d01c4baf13e04e1a789", "gitDir": "test/corpus/repos/javascript", - "sha2": "0a38cbb0dc46ccdf6a85eb82cfd1702afb266bac" + "sha2": "20bc26cc8af9efd835b023b026250f920bf1cc88" }] diff --git a/test/corpus/diff-summaries/javascript/class.json b/test/corpus/diff-summaries/javascript/class.json index 26cdd043e..5df1a0a05 100644 --- a/test/corpus/diff-summaries/javascript/class.json +++ b/test/corpus/diff-summaries/javascript/class.json @@ -27,9 +27,9 @@ "filePaths": [ "class.js" ], - "sha1": "2a461fb53b242f9515049235816a7a7b018ed3d7", + "sha1": "a73251e778f05b8cbe501d5f6ea0c483640ced20", "gitDir": "test/corpus/repos/javascript", - "sha2": "dddabcf5ab7dbc40c842a749eb8e46a1de6b57bb" + "sha2": "d14f6c7cb29e72223e5d2c7170379f99f8a893b2" } ,{ "testCaseDescription": "javascript-class-replacement-insert-test", @@ -77,9 +77,9 @@ "filePaths": [ "class.js" ], - "sha1": "dddabcf5ab7dbc40c842a749eb8e46a1de6b57bb", + "sha1": "d14f6c7cb29e72223e5d2c7170379f99f8a893b2", "gitDir": "test/corpus/repos/javascript", - "sha2": "a1fc66c039e65c787ba76b0f53e475bd3b185c29" + "sha2": "7c73aea04cb45042bf232a448d426be9ae888a9b" } ,{ "testCaseDescription": "javascript-class-delete-insert-test", @@ -183,9 +183,9 @@ "filePaths": [ "class.js" ], - "sha1": "a1fc66c039e65c787ba76b0f53e475bd3b185c29", + "sha1": "7c73aea04cb45042bf232a448d426be9ae888a9b", "gitDir": "test/corpus/repos/javascript", - "sha2": "e50409c326c15ea435bd958f942068f85890cd88" + "sha2": "aecfbbcd53407a567f46a40cad9270e0bf22458a" } ,{ "testCaseDescription": "javascript-class-replacement-test", @@ -289,9 +289,9 @@ "filePaths": [ "class.js" ], - "sha1": "e50409c326c15ea435bd958f942068f85890cd88", + "sha1": "aecfbbcd53407a567f46a40cad9270e0bf22458a", "gitDir": "test/corpus/repos/javascript", - "sha2": "48709d8e52b535873dc17daa85dde24d4375ca24" + "sha2": "f35ad41e7a506af4049a99149a8f42fe403fd3c2" } ,{ "testCaseDescription": "javascript-class-delete-replacement-test", @@ -356,9 +356,9 @@ "filePaths": [ "class.js" ], - "sha1": "48709d8e52b535873dc17daa85dde24d4375ca24", + "sha1": "f35ad41e7a506af4049a99149a8f42fe403fd3c2", "gitDir": "test/corpus/repos/javascript", - "sha2": "e6e1d37e807c2fc0cb28a9df20f8dc3dbaeb575b" + "sha2": "408c1f0028eff597ce2334d8b98a0692fbc32ee2" } ,{ "testCaseDescription": "javascript-class-delete-test", @@ -389,9 +389,9 @@ "filePaths": [ "class.js" ], - "sha1": "e6e1d37e807c2fc0cb28a9df20f8dc3dbaeb575b", + "sha1": "408c1f0028eff597ce2334d8b98a0692fbc32ee2", "gitDir": "test/corpus/repos/javascript", - "sha2": "9d37c9ad21bb56f2ad789193714d422cb4a214bb" + "sha2": "1414ce434ca9fe4f8b0cdfb16e7e50bcdd12055f" } ,{ "testCaseDescription": "javascript-class-delete-rest-test", @@ -422,7 +422,7 @@ "filePaths": [ "class.js" ], - "sha1": "9d37c9ad21bb56f2ad789193714d422cb4a214bb", + "sha1": "1414ce434ca9fe4f8b0cdfb16e7e50bcdd12055f", "gitDir": "test/corpus/repos/javascript", - "sha2": "54c26c85b1720507e7c076553120465986fd2894" + "sha2": "04b681e1190310f6148595f3d80260ae13299d43" }] diff --git a/test/corpus/diff-summaries/javascript/comma-operator.json b/test/corpus/diff-summaries/javascript/comma-operator.json index a423f54b3..dfba42dc6 100644 --- a/test/corpus/diff-summaries/javascript/comma-operator.json +++ b/test/corpus/diff-summaries/javascript/comma-operator.json @@ -44,9 +44,9 @@ "filePaths": [ "comma-operator.js" ], - "sha1": "439dff969c87787fe222d1721433c8fafb0f1a89", + "sha1": "462756b98c54f0b7551f56ee43c309cf51fd64a2", "gitDir": "test/corpus/repos/javascript", - "sha2": "9b1421eae5e42d1179865f793c365323e50dcf75" + "sha2": "9302084f6e6aa45c6f4f21f362c0fdc2f5ee9789" } ,{ "testCaseDescription": "javascript-comma-operator-replacement-insert-test", @@ -111,9 +111,9 @@ "filePaths": [ "comma-operator.js" ], - "sha1": "9b1421eae5e42d1179865f793c365323e50dcf75", + "sha1": "9302084f6e6aa45c6f4f21f362c0fdc2f5ee9789", "gitDir": "test/corpus/repos/javascript", - "sha2": "dc4d656591b9a5551f8d4eed7bcced3e77c96ced" + "sha2": "664fefa1822fe80ff2b7f48c3bdaf380b8efce49" } ,{ "testCaseDescription": "javascript-comma-operator-delete-insert-test", @@ -178,9 +178,9 @@ "filePaths": [ "comma-operator.js" ], - "sha1": "dc4d656591b9a5551f8d4eed7bcced3e77c96ced", + "sha1": "664fefa1822fe80ff2b7f48c3bdaf380b8efce49", "gitDir": "test/corpus/repos/javascript", - "sha2": "c44075bf65a6c67bb986ddba4014f966f5ed6cf3" + "sha2": "209e54cd2325e3b40e4fb2429bbdd353cb11df96" } ,{ "testCaseDescription": "javascript-comma-operator-replacement-test", @@ -245,9 +245,9 @@ "filePaths": [ "comma-operator.js" ], - "sha1": "c44075bf65a6c67bb986ddba4014f966f5ed6cf3", + "sha1": "209e54cd2325e3b40e4fb2429bbdd353cb11df96", "gitDir": "test/corpus/repos/javascript", - "sha2": "bc41fdf79f37384007f19a2bf95b6bc49bacd024" + "sha2": "a396a8a09fff584b6cd8c3053f9bceee805e6ac3" } ,{ "testCaseDescription": "javascript-comma-operator-delete-replacement-test", @@ -329,9 +329,9 @@ "filePaths": [ "comma-operator.js" ], - "sha1": "bc41fdf79f37384007f19a2bf95b6bc49bacd024", + "sha1": "a396a8a09fff584b6cd8c3053f9bceee805e6ac3", "gitDir": "test/corpus/repos/javascript", - "sha2": "c07faa49cd9c2089755489d8f4b576a8f171de03" + "sha2": "438aa8fe676d5ddfeff0b8826369de84c9dc8c92" } ,{ "testCaseDescription": "javascript-comma-operator-delete-test", @@ -379,9 +379,9 @@ "filePaths": [ "comma-operator.js" ], - "sha1": "c07faa49cd9c2089755489d8f4b576a8f171de03", + "sha1": "438aa8fe676d5ddfeff0b8826369de84c9dc8c92", "gitDir": "test/corpus/repos/javascript", - "sha2": "d48db63fb39e2dfe3cd592fc59edc4933d74b289" + "sha2": "81c1a2f1b83654c6fadb49a595a94dbddde129ab" } ,{ "testCaseDescription": "javascript-comma-operator-delete-rest-test", @@ -412,7 +412,7 @@ "filePaths": [ "comma-operator.js" ], - "sha1": "d48db63fb39e2dfe3cd592fc59edc4933d74b289", + "sha1": "81c1a2f1b83654c6fadb49a595a94dbddde129ab", "gitDir": "test/corpus/repos/javascript", - "sha2": "62499db349bd96eba99a785f67d473de8d5b99e6" + "sha2": "e9872de5faf687bc02c8b7a06031ef152b2d3dbe" }] diff --git a/test/corpus/diff-summaries/javascript/comment.json b/test/corpus/diff-summaries/javascript/comment.json index 959ebcf84..6c8a07265 100644 --- a/test/corpus/diff-summaries/javascript/comment.json +++ b/test/corpus/diff-summaries/javascript/comment.json @@ -27,9 +27,9 @@ "filePaths": [ "comment.js" ], - "sha1": "7c4be6139148ad009e9bf49df1952b9abe45aee0", + "sha1": "61540dc73cfaad0786519aca74727ab895384c00", "gitDir": "test/corpus/repos/javascript", - "sha2": "58661d0321373ae169d680373f5abeaa9edaf526" + "sha2": "93f50d2243f8c7646daf8fddb830df53de42d8f5" } ,{ "testCaseDescription": "javascript-comment-replacement-insert-test", @@ -77,9 +77,9 @@ "filePaths": [ "comment.js" ], - "sha1": "58661d0321373ae169d680373f5abeaa9edaf526", + "sha1": "93f50d2243f8c7646daf8fddb830df53de42d8f5", "gitDir": "test/corpus/repos/javascript", - "sha2": "6eea53ca3e63db2b8073403ee4dd76fc280d650c" + "sha2": "3ee6b1b429b8805f1051cbc143cc64d9462ba4d5" } ,{ "testCaseDescription": "javascript-comment-delete-insert-test", @@ -123,9 +123,9 @@ "filePaths": [ "comment.js" ], - "sha1": "6eea53ca3e63db2b8073403ee4dd76fc280d650c", + "sha1": "3ee6b1b429b8805f1051cbc143cc64d9462ba4d5", "gitDir": "test/corpus/repos/javascript", - "sha2": "8fbe23ec43ee1b6b4275658522fed08ca021f0ea" + "sha2": "8873c3149ab63a064d4b6e59d9bab7b7e2c1da68" } ,{ "testCaseDescription": "javascript-comment-replacement-test", @@ -169,9 +169,9 @@ "filePaths": [ "comment.js" ], - "sha1": "8fbe23ec43ee1b6b4275658522fed08ca021f0ea", + "sha1": "8873c3149ab63a064d4b6e59d9bab7b7e2c1da68", "gitDir": "test/corpus/repos/javascript", - "sha2": "95f13e0e9465d96342006bb4704235cc74661270" + "sha2": "ce476dad66521fd00c2643b33d27d97f0ea06dc5" } ,{ "testCaseDescription": "javascript-comment-delete-replacement-test", @@ -236,9 +236,9 @@ "filePaths": [ "comment.js" ], - "sha1": "95f13e0e9465d96342006bb4704235cc74661270", + "sha1": "ce476dad66521fd00c2643b33d27d97f0ea06dc5", "gitDir": "test/corpus/repos/javascript", - "sha2": "5b92ecdf3967f913ce0e5463eeda1f886ea0ea9f" + "sha2": "fae5624ac16f834275314d94ff7584a48542f0b5" } ,{ "testCaseDescription": "javascript-comment-delete-test", @@ -269,9 +269,9 @@ "filePaths": [ "comment.js" ], - "sha1": "5b92ecdf3967f913ce0e5463eeda1f886ea0ea9f", + "sha1": "fae5624ac16f834275314d94ff7584a48542f0b5", "gitDir": "test/corpus/repos/javascript", - "sha2": "66a2757872c04101d7068896951e5125ae93a2b2" + "sha2": "bfcfebda701bcee0da94c64a24d5ca11a03270df" } ,{ "testCaseDescription": "javascript-comment-delete-rest-test", @@ -302,7 +302,7 @@ "filePaths": [ "comment.js" ], - "sha1": "66a2757872c04101d7068896951e5125ae93a2b2", + "sha1": "bfcfebda701bcee0da94c64a24d5ca11a03270df", "gitDir": "test/corpus/repos/javascript", - "sha2": "011a5d6edc417ef0abbfb325ad08abdb917f4184" + "sha2": "7d081d5591b64adba332f89a0a3aeba494aa1b0e" }] diff --git a/test/corpus/diff-summaries/javascript/constructor-call.json b/test/corpus/diff-summaries/javascript/constructor-call.json index 5e91677e8..74791a7ea 100644 --- a/test/corpus/diff-summaries/javascript/constructor-call.json +++ b/test/corpus/diff-summaries/javascript/constructor-call.json @@ -27,9 +27,9 @@ "filePaths": [ "constructor-call.js" ], - "sha1": "2ad39701c647bc8063509309d3cc04d0c6adf0e8", + "sha1": "f110a993d59a58f31e4b09bd46734026c4fdcc60", "gitDir": "test/corpus/repos/javascript", - "sha2": "5114d1974e68a6eb9a6826a3f7135c9c62ed3e6b" + "sha2": "c84bb50f8570d3b7620847bb6e53e5164da5dc97" } ,{ "testCaseDescription": "javascript-constructor-call-replacement-insert-test", @@ -77,9 +77,9 @@ "filePaths": [ "constructor-call.js" ], - "sha1": "5114d1974e68a6eb9a6826a3f7135c9c62ed3e6b", + "sha1": "c84bb50f8570d3b7620847bb6e53e5164da5dc97", "gitDir": "test/corpus/repos/javascript", - "sha2": "5663c1423deefd3baaf595257ed0bf2d40a914c0" + "sha2": "f95378398761e820b287651f61214cdaa4d087dd" } ,{ "testCaseDescription": "javascript-constructor-call-delete-insert-test", @@ -123,9 +123,9 @@ "filePaths": [ "constructor-call.js" ], - "sha1": "5663c1423deefd3baaf595257ed0bf2d40a914c0", + "sha1": "f95378398761e820b287651f61214cdaa4d087dd", "gitDir": "test/corpus/repos/javascript", - "sha2": "7fc56a50d01d51c2e5317da1199db6d4917bd76e" + "sha2": "a24d6951b26950920f325e14e492a751fd96c459" } ,{ "testCaseDescription": "javascript-constructor-call-replacement-test", @@ -169,9 +169,9 @@ "filePaths": [ "constructor-call.js" ], - "sha1": "7fc56a50d01d51c2e5317da1199db6d4917bd76e", + "sha1": "a24d6951b26950920f325e14e492a751fd96c459", "gitDir": "test/corpus/repos/javascript", - "sha2": "076dec34cc2e402d97eb7f28c2167e1425168ca2" + "sha2": "c8e18957750cdeed01b76272ae9dece10cc92bf4" } ,{ "testCaseDescription": "javascript-constructor-call-delete-replacement-test", @@ -236,9 +236,9 @@ "filePaths": [ "constructor-call.js" ], - "sha1": "076dec34cc2e402d97eb7f28c2167e1425168ca2", + "sha1": "c8e18957750cdeed01b76272ae9dece10cc92bf4", "gitDir": "test/corpus/repos/javascript", - "sha2": "53aeb6fee431b481021c69c3e9c59733ad171da6" + "sha2": "9be694183bf6de1655a6be394bf43f07f90b1bef" } ,{ "testCaseDescription": "javascript-constructor-call-delete-test", @@ -269,9 +269,9 @@ "filePaths": [ "constructor-call.js" ], - "sha1": "53aeb6fee431b481021c69c3e9c59733ad171da6", + "sha1": "9be694183bf6de1655a6be394bf43f07f90b1bef", "gitDir": "test/corpus/repos/javascript", - "sha2": "030f395167154c094dba05ae435468a795ff7ecb" + "sha2": "cbfcfc8f787243ede41b2cc3703a90986c2cbd64" } ,{ "testCaseDescription": "javascript-constructor-call-delete-rest-test", @@ -302,7 +302,7 @@ "filePaths": [ "constructor-call.js" ], - "sha1": "030f395167154c094dba05ae435468a795ff7ecb", + "sha1": "cbfcfc8f787243ede41b2cc3703a90986c2cbd64", "gitDir": "test/corpus/repos/javascript", - "sha2": "ebf93ce214fd99b995fc859da2c899eaf98b003a" + "sha2": "952d18ccd1d4413a1252458befbb6593253aa794" }] diff --git a/test/corpus/diff-summaries/javascript/delete-operator.json b/test/corpus/diff-summaries/javascript/delete-operator.json index 23df7b0d9..03be6125e 100644 --- a/test/corpus/diff-summaries/javascript/delete-operator.json +++ b/test/corpus/diff-summaries/javascript/delete-operator.json @@ -27,9 +27,9 @@ "filePaths": [ "delete-operator.js" ], - "sha1": "ba1f4c979646df1521e9a187cc24c8b8afc3cd24", + "sha1": "1d2c6fd4f13c50341f68aa3be753d5748c072f12", "gitDir": "test/corpus/repos/javascript", - "sha2": "22b408a5efa333a6a8d9eb9221c6d158da79b97a" + "sha2": "79d9ba3ad4cb2029c5a611275136bb722cdd1e16" } ,{ "testCaseDescription": "javascript-delete-operator-replacement-insert-test", @@ -77,9 +77,9 @@ "filePaths": [ "delete-operator.js" ], - "sha1": "22b408a5efa333a6a8d9eb9221c6d158da79b97a", + "sha1": "79d9ba3ad4cb2029c5a611275136bb722cdd1e16", "gitDir": "test/corpus/repos/javascript", - "sha2": "c8bb0986f68e4a877c005a52b97594cf548cf60a" + "sha2": "92ece167d0e443f1ec929261dc1ec23c1373ef36" } ,{ "testCaseDescription": "javascript-delete-operator-delete-insert-test", @@ -123,9 +123,9 @@ "filePaths": [ "delete-operator.js" ], - "sha1": "c8bb0986f68e4a877c005a52b97594cf548cf60a", + "sha1": "92ece167d0e443f1ec929261dc1ec23c1373ef36", "gitDir": "test/corpus/repos/javascript", - "sha2": "4616b0eb947d61ab5f859fcd16067da2f6d73c10" + "sha2": "e5f4a3669771a2906494327404537d35b5a64586" } ,{ "testCaseDescription": "javascript-delete-operator-replacement-test", @@ -169,9 +169,9 @@ "filePaths": [ "delete-operator.js" ], - "sha1": "4616b0eb947d61ab5f859fcd16067da2f6d73c10", + "sha1": "e5f4a3669771a2906494327404537d35b5a64586", "gitDir": "test/corpus/repos/javascript", - "sha2": "bdd2a3aa22441e4f32c6423cca49f16b1003caaf" + "sha2": "a41fba80ce5541212c1d9e857994ff32798ffc5b" } ,{ "testCaseDescription": "javascript-delete-operator-delete-replacement-test", @@ -236,9 +236,9 @@ "filePaths": [ "delete-operator.js" ], - "sha1": "bdd2a3aa22441e4f32c6423cca49f16b1003caaf", + "sha1": "a41fba80ce5541212c1d9e857994ff32798ffc5b", "gitDir": "test/corpus/repos/javascript", - "sha2": "58411bd05b3352bcc84f5d298a003cd1dfac51db" + "sha2": "53fc1797fbb60e86e31bc8700953d1226c3c5378" } ,{ "testCaseDescription": "javascript-delete-operator-delete-test", @@ -269,9 +269,9 @@ "filePaths": [ "delete-operator.js" ], - "sha1": "58411bd05b3352bcc84f5d298a003cd1dfac51db", + "sha1": "53fc1797fbb60e86e31bc8700953d1226c3c5378", "gitDir": "test/corpus/repos/javascript", - "sha2": "f6400b281b3ff58773e3fcc1e7cd8ceafef368d3" + "sha2": "2df353078b8e0e73d9bc954808c567675203a143" } ,{ "testCaseDescription": "javascript-delete-operator-delete-rest-test", @@ -302,7 +302,7 @@ "filePaths": [ "delete-operator.js" ], - "sha1": "f6400b281b3ff58773e3fcc1e7cd8ceafef368d3", + "sha1": "2df353078b8e0e73d9bc954808c567675203a143", "gitDir": "test/corpus/repos/javascript", - "sha2": "9b9215fdd0036d2a74bfc6a6c4b43187e3ad3ef8" + "sha2": "f8fceed82b3d3f5189fd21d8dd7a5589c803ba0e" }] diff --git a/test/corpus/diff-summaries/javascript/do-while-statement.json b/test/corpus/diff-summaries/javascript/do-while-statement.json index 11cc885e8..7ea918035 100644 --- a/test/corpus/diff-summaries/javascript/do-while-statement.json +++ b/test/corpus/diff-summaries/javascript/do-while-statement.json @@ -27,9 +27,9 @@ "filePaths": [ "do-while-statement.js" ], - "sha1": "101c947313c24c2e76769c572c080adea44c80da", + "sha1": "ea67bdfe9d16bfb0ba0858898f969294740b84fb", "gitDir": "test/corpus/repos/javascript", - "sha2": "93936ed87065031f73b74f8be77314335ecd7cd9" + "sha2": "1edeabe5a69e92387c0327d8782bfed7afe44ca0" } ,{ "testCaseDescription": "javascript-do-while-statement-replacement-insert-test", @@ -77,9 +77,9 @@ "filePaths": [ "do-while-statement.js" ], - "sha1": "93936ed87065031f73b74f8be77314335ecd7cd9", + "sha1": "1edeabe5a69e92387c0327d8782bfed7afe44ca0", "gitDir": "test/corpus/repos/javascript", - "sha2": "e9de7cb5a587ed02a47bcd9fab126ec64929f1aa" + "sha2": "95cef4798ecd89a3a1756f9804ae3c0fa66002b9" } ,{ "testCaseDescription": "javascript-do-while-statement-delete-insert-test", @@ -153,9 +153,9 @@ "filePaths": [ "do-while-statement.js" ], - "sha1": "e9de7cb5a587ed02a47bcd9fab126ec64929f1aa", + "sha1": "95cef4798ecd89a3a1756f9804ae3c0fa66002b9", "gitDir": "test/corpus/repos/javascript", - "sha2": "fc875ea9de56cf36209363fbbcfba7d7f8b99a1c" + "sha2": "fe98c3543d4760b39db8064ba952a382afe9a3b7" } ,{ "testCaseDescription": "javascript-do-while-statement-replacement-test", @@ -229,9 +229,9 @@ "filePaths": [ "do-while-statement.js" ], - "sha1": "fc875ea9de56cf36209363fbbcfba7d7f8b99a1c", + "sha1": "fe98c3543d4760b39db8064ba952a382afe9a3b7", "gitDir": "test/corpus/repos/javascript", - "sha2": "f84c5d87ee8b4610e69f3adc8df2431ba8f49925" + "sha2": "32e82efe60602edf29f95d10568c93cbd8f6d789" } ,{ "testCaseDescription": "javascript-do-while-statement-delete-replacement-test", @@ -296,9 +296,9 @@ "filePaths": [ "do-while-statement.js" ], - "sha1": "f84c5d87ee8b4610e69f3adc8df2431ba8f49925", + "sha1": "32e82efe60602edf29f95d10568c93cbd8f6d789", "gitDir": "test/corpus/repos/javascript", - "sha2": "97f785d41e9c18cc05f6448c76686f01ea910c39" + "sha2": "c7b0f597290d3b8a918a0c60dfed1fe05e9af91a" } ,{ "testCaseDescription": "javascript-do-while-statement-delete-test", @@ -329,9 +329,9 @@ "filePaths": [ "do-while-statement.js" ], - "sha1": "97f785d41e9c18cc05f6448c76686f01ea910c39", + "sha1": "c7b0f597290d3b8a918a0c60dfed1fe05e9af91a", "gitDir": "test/corpus/repos/javascript", - "sha2": "27f0e253d26f01785aa481b298e72590f8f193da" + "sha2": "e0a76f9216bff7d64d708ad50a33d408ef885d55" } ,{ "testCaseDescription": "javascript-do-while-statement-delete-rest-test", @@ -362,7 +362,7 @@ "filePaths": [ "do-while-statement.js" ], - "sha1": "27f0e253d26f01785aa481b298e72590f8f193da", + "sha1": "e0a76f9216bff7d64d708ad50a33d408ef885d55", "gitDir": "test/corpus/repos/javascript", - "sha2": "c2a48d97ae6754bf21e1dbfa2e13bde3f68deb9c" + "sha2": "fd292d1b33fb3253b0d0f66bae29de22c247d85c" }] diff --git a/test/corpus/diff-summaries/javascript/false.json b/test/corpus/diff-summaries/javascript/false.json index ad4940d87..3c56aae07 100644 --- a/test/corpus/diff-summaries/javascript/false.json +++ b/test/corpus/diff-summaries/javascript/false.json @@ -27,9 +27,9 @@ "filePaths": [ "false.js" ], - "sha1": "0cad1bc8f133de3ec0a2bff083b413422673bbb7", + "sha1": "d72ebc215a9377983c2463fd424f608320626141", "gitDir": "test/corpus/repos/javascript", - "sha2": "f4a3023cecb97a83e81f0b674de98c9f764a6057" + "sha2": "240ba155f4a0d96494076ac592383350d2743fb6" } ,{ "testCaseDescription": "javascript-false-replacement-insert-test", @@ -77,9 +77,9 @@ "filePaths": [ "false.js" ], - "sha1": "f4a3023cecb97a83e81f0b674de98c9f764a6057", + "sha1": "240ba155f4a0d96494076ac592383350d2743fb6", "gitDir": "test/corpus/repos/javascript", - "sha2": "548d690ca10714f0a92c5a3d8fd3884b2f617088" + "sha2": "754a612c9706e0a510e018e4c450fe4fe1187efc" } ,{ "testCaseDescription": "javascript-false-delete-insert-test", @@ -127,9 +127,9 @@ "filePaths": [ "false.js" ], - "sha1": "548d690ca10714f0a92c5a3d8fd3884b2f617088", + "sha1": "754a612c9706e0a510e018e4c450fe4fe1187efc", "gitDir": "test/corpus/repos/javascript", - "sha2": "3cd2a6fd547555f9688312759b68a9dbd98418af" + "sha2": "0bc6cba1b1ef9e8b8cabc8113a015441a7f8b690" } ,{ "testCaseDescription": "javascript-false-replacement-test", @@ -177,9 +177,9 @@ "filePaths": [ "false.js" ], - "sha1": "3cd2a6fd547555f9688312759b68a9dbd98418af", + "sha1": "0bc6cba1b1ef9e8b8cabc8113a015441a7f8b690", "gitDir": "test/corpus/repos/javascript", - "sha2": "f010b4e20d7b0b41f58b23c815ff2564ef7657e3" + "sha2": "8a8271e57bb0d9af3a3137170449e27344a574fb" } ,{ "testCaseDescription": "javascript-false-delete-replacement-test", @@ -244,9 +244,9 @@ "filePaths": [ "false.js" ], - "sha1": "f010b4e20d7b0b41f58b23c815ff2564ef7657e3", + "sha1": "8a8271e57bb0d9af3a3137170449e27344a574fb", "gitDir": "test/corpus/repos/javascript", - "sha2": "64b12cb4eca55960d98f1bb66c121b7f26701a0b" + "sha2": "94d9fd3e963a5ff7aecd77f21e25e423a0d991bf" } ,{ "testCaseDescription": "javascript-false-delete-test", @@ -277,9 +277,9 @@ "filePaths": [ "false.js" ], - "sha1": "64b12cb4eca55960d98f1bb66c121b7f26701a0b", + "sha1": "94d9fd3e963a5ff7aecd77f21e25e423a0d991bf", "gitDir": "test/corpus/repos/javascript", - "sha2": "34dbc99b39acb62b2babc1773d707f87331aa6e5" + "sha2": "e1b3d5f5c03327df610744915e4ae73b5e2af1d0" } ,{ "testCaseDescription": "javascript-false-delete-rest-test", @@ -310,7 +310,7 @@ "filePaths": [ "false.js" ], - "sha1": "34dbc99b39acb62b2babc1773d707f87331aa6e5", + "sha1": "e1b3d5f5c03327df610744915e4ae73b5e2af1d0", "gitDir": "test/corpus/repos/javascript", - "sha2": "2a461fb53b242f9515049235816a7a7b018ed3d7" + "sha2": "a73251e778f05b8cbe501d5f6ea0c483640ced20" }] diff --git a/test/corpus/diff-summaries/javascript/for-in-statement.json b/test/corpus/diff-summaries/javascript/for-in-statement.json index 0ab172fb7..e63d5e4b5 100644 --- a/test/corpus/diff-summaries/javascript/for-in-statement.json +++ b/test/corpus/diff-summaries/javascript/for-in-statement.json @@ -27,9 +27,9 @@ "filePaths": [ "for-in-statement.js" ], - "sha1": "17aa0b04103d8aaedf77c3ff72f699f18194a962", + "sha1": "7fe4e0b214260f0482129909a00b5146e3bfc1da", "gitDir": "test/corpus/repos/javascript", - "sha2": "e84def0e1a12e34c85dcec7af88b964eeb198e63" + "sha2": "6bab84255f645c5440731291f1b3e2405e608dcb" } ,{ "testCaseDescription": "javascript-for-in-statement-replacement-insert-test", @@ -77,9 +77,9 @@ "filePaths": [ "for-in-statement.js" ], - "sha1": "e84def0e1a12e34c85dcec7af88b964eeb198e63", + "sha1": "6bab84255f645c5440731291f1b3e2405e608dcb", "gitDir": "test/corpus/repos/javascript", - "sha2": "f4ea564697dda7f2cc02fe16c0879aeb5952ddc2" + "sha2": "229e0057d54bdb3dddabd1b1f4c5b520dc7b5617" } ,{ "testCaseDescription": "javascript-for-in-statement-delete-insert-test", @@ -183,9 +183,9 @@ "filePaths": [ "for-in-statement.js" ], - "sha1": "f4ea564697dda7f2cc02fe16c0879aeb5952ddc2", + "sha1": "229e0057d54bdb3dddabd1b1f4c5b520dc7b5617", "gitDir": "test/corpus/repos/javascript", - "sha2": "9e92b2178f4fec83f11e97e548ff1e4c438df489" + "sha2": "db98b8a60e7b0eeac50e68d6b4b5c8d4f557ca9e" } ,{ "testCaseDescription": "javascript-for-in-statement-replacement-test", @@ -289,9 +289,9 @@ "filePaths": [ "for-in-statement.js" ], - "sha1": "9e92b2178f4fec83f11e97e548ff1e4c438df489", + "sha1": "db98b8a60e7b0eeac50e68d6b4b5c8d4f557ca9e", "gitDir": "test/corpus/repos/javascript", - "sha2": "fa62d70d1bf140a2a4339ac3b0811e3bed1eb9d5" + "sha2": "35dffb6c595ca8dbd5e2d557271f29b573177e79" } ,{ "testCaseDescription": "javascript-for-in-statement-delete-replacement-test", @@ -356,9 +356,9 @@ "filePaths": [ "for-in-statement.js" ], - "sha1": "fa62d70d1bf140a2a4339ac3b0811e3bed1eb9d5", + "sha1": "35dffb6c595ca8dbd5e2d557271f29b573177e79", "gitDir": "test/corpus/repos/javascript", - "sha2": "6eb412c429997ade58d7a15e880562076bfb9517" + "sha2": "ad88456eafdc0e88fec2dc3677bfcc5c7f37c310" } ,{ "testCaseDescription": "javascript-for-in-statement-delete-test", @@ -389,9 +389,9 @@ "filePaths": [ "for-in-statement.js" ], - "sha1": "6eb412c429997ade58d7a15e880562076bfb9517", + "sha1": "ad88456eafdc0e88fec2dc3677bfcc5c7f37c310", "gitDir": "test/corpus/repos/javascript", - "sha2": "0fead3b4746ae5344c4a240e1e177146ec3ada81" + "sha2": "13399a918cf13accf13f9001b70995b677ba4467" } ,{ "testCaseDescription": "javascript-for-in-statement-delete-rest-test", @@ -422,7 +422,7 @@ "filePaths": [ "for-in-statement.js" ], - "sha1": "0fead3b4746ae5344c4a240e1e177146ec3ada81", + "sha1": "13399a918cf13accf13f9001b70995b677ba4467", "gitDir": "test/corpus/repos/javascript", - "sha2": "0ae77f84b193044495c0abfc49d346bde5e39414" + "sha2": "ff9c3e1416340f9c41efe59880ae44b658ff4bf3" }] diff --git a/test/corpus/diff-summaries/javascript/for-loop-with-in-statement.json b/test/corpus/diff-summaries/javascript/for-loop-with-in-statement.json index 17d54119e..b7b5dc45d 100644 --- a/test/corpus/diff-summaries/javascript/for-loop-with-in-statement.json +++ b/test/corpus/diff-summaries/javascript/for-loop-with-in-statement.json @@ -27,9 +27,9 @@ "filePaths": [ "for-loop-with-in-statement.js" ], - "sha1": "195a1d9a04af2cce44e8af09913140e80af6656f", + "sha1": "b0363eb07d0284130aab04183573dcd31fa7f221", "gitDir": "test/corpus/repos/javascript", - "sha2": "7d1d4882288053a383c3aa95e23e9984182f32d0" + "sha2": "bd70642d89f84aa72ff6781a2b22c82b345ac1d5" } ,{ "testCaseDescription": "javascript-for-loop-with-in-statement-replacement-insert-test", @@ -77,9 +77,9 @@ "filePaths": [ "for-loop-with-in-statement.js" ], - "sha1": "7d1d4882288053a383c3aa95e23e9984182f32d0", + "sha1": "bd70642d89f84aa72ff6781a2b22c82b345ac1d5", "gitDir": "test/corpus/repos/javascript", - "sha2": "b92a7a77b05f33eb98feb0b56335dc0e9abb3eef" + "sha2": "337a282c5bfdde568b4b1431a6259fd1e187d897" } ,{ "testCaseDescription": "javascript-for-loop-with-in-statement-delete-insert-test", @@ -153,9 +153,9 @@ "filePaths": [ "for-loop-with-in-statement.js" ], - "sha1": "b92a7a77b05f33eb98feb0b56335dc0e9abb3eef", + "sha1": "337a282c5bfdde568b4b1431a6259fd1e187d897", "gitDir": "test/corpus/repos/javascript", - "sha2": "317015fd398ef080136c5200ab496ce236ec85d6" + "sha2": "b6039e1333c1772e592e7dc27a94de22b1323bb5" } ,{ "testCaseDescription": "javascript-for-loop-with-in-statement-replacement-test", @@ -229,9 +229,9 @@ "filePaths": [ "for-loop-with-in-statement.js" ], - "sha1": "317015fd398ef080136c5200ab496ce236ec85d6", + "sha1": "b6039e1333c1772e592e7dc27a94de22b1323bb5", "gitDir": "test/corpus/repos/javascript", - "sha2": "ce83a72b91d364110f8c0b19b8db6de0d7dbe799" + "sha2": "0a764d4fa36759c678501ca540fc99713b41420a" } ,{ "testCaseDescription": "javascript-for-loop-with-in-statement-delete-replacement-test", @@ -296,9 +296,9 @@ "filePaths": [ "for-loop-with-in-statement.js" ], - "sha1": "ce83a72b91d364110f8c0b19b8db6de0d7dbe799", + "sha1": "0a764d4fa36759c678501ca540fc99713b41420a", "gitDir": "test/corpus/repos/javascript", - "sha2": "4172e6ed8b75daaad3d5e914b048dca9ea598557" + "sha2": "9fa99c92ac72ad519a3b1f2b5d93a5537d435a92" } ,{ "testCaseDescription": "javascript-for-loop-with-in-statement-delete-test", @@ -329,9 +329,9 @@ "filePaths": [ "for-loop-with-in-statement.js" ], - "sha1": "4172e6ed8b75daaad3d5e914b048dca9ea598557", + "sha1": "9fa99c92ac72ad519a3b1f2b5d93a5537d435a92", "gitDir": "test/corpus/repos/javascript", - "sha2": "c9ba7b286fbdb4cb5edb69dfd845ff4f0c7ef0ec" + "sha2": "cbc52bfd4415f0b6ade8e057dc28ea23bb4525de" } ,{ "testCaseDescription": "javascript-for-loop-with-in-statement-delete-rest-test", @@ -362,7 +362,7 @@ "filePaths": [ "for-loop-with-in-statement.js" ], - "sha1": "c9ba7b286fbdb4cb5edb69dfd845ff4f0c7ef0ec", + "sha1": "cbc52bfd4415f0b6ade8e057dc28ea23bb4525de", "gitDir": "test/corpus/repos/javascript", - "sha2": "dbba8dcf3e630c86fb6e8eddc4fc93408e550277" + "sha2": "78d8fd6fdf97f596e0c6c4c7f4a6661bc3ffa357" }] diff --git a/test/corpus/diff-summaries/javascript/for-of-statement.json b/test/corpus/diff-summaries/javascript/for-of-statement.json index 4350b1a5e..8368ad1d4 100644 --- a/test/corpus/diff-summaries/javascript/for-of-statement.json +++ b/test/corpus/diff-summaries/javascript/for-of-statement.json @@ -27,9 +27,9 @@ "filePaths": [ "for-of-statement.js" ], - "sha1": "dbba8dcf3e630c86fb6e8eddc4fc93408e550277", + "sha1": "78d8fd6fdf97f596e0c6c4c7f4a6661bc3ffa357", "gitDir": "test/corpus/repos/javascript", - "sha2": "e9daa8391a6b17f0fd238b55abfae4778eed9249" + "sha2": "70584f81e9913597b116943cebc3749db173209f" } ,{ "testCaseDescription": "javascript-for-of-statement-replacement-insert-test", @@ -77,9 +77,9 @@ "filePaths": [ "for-of-statement.js" ], - "sha1": "e9daa8391a6b17f0fd238b55abfae4778eed9249", + "sha1": "70584f81e9913597b116943cebc3749db173209f", "gitDir": "test/corpus/repos/javascript", - "sha2": "1e2381938a88e94e3f8f1cfdf6d44b24ca2cf0f4" + "sha2": "c45a6d3219e4221bd27fbee1b42e709cf8bd02c7" } ,{ "testCaseDescription": "javascript-for-of-statement-delete-insert-test", @@ -183,9 +183,9 @@ "filePaths": [ "for-of-statement.js" ], - "sha1": "1e2381938a88e94e3f8f1cfdf6d44b24ca2cf0f4", + "sha1": "c45a6d3219e4221bd27fbee1b42e709cf8bd02c7", "gitDir": "test/corpus/repos/javascript", - "sha2": "b6fa78c74f9e8387335a3d83ad88f4527cb90bd9" + "sha2": "a5ca7dcb73c029d81d8d5dc393828d7d7674fbca" } ,{ "testCaseDescription": "javascript-for-of-statement-replacement-test", @@ -289,9 +289,9 @@ "filePaths": [ "for-of-statement.js" ], - "sha1": "b6fa78c74f9e8387335a3d83ad88f4527cb90bd9", + "sha1": "a5ca7dcb73c029d81d8d5dc393828d7d7674fbca", "gitDir": "test/corpus/repos/javascript", - "sha2": "3486a1725bd6dae3a69b5eea6a6580838211acaa" + "sha2": "19da16ae29c9cfbc2a47cd92a14fb09c20408e22" } ,{ "testCaseDescription": "javascript-for-of-statement-delete-replacement-test", @@ -356,9 +356,9 @@ "filePaths": [ "for-of-statement.js" ], - "sha1": "3486a1725bd6dae3a69b5eea6a6580838211acaa", + "sha1": "19da16ae29c9cfbc2a47cd92a14fb09c20408e22", "gitDir": "test/corpus/repos/javascript", - "sha2": "202a08ba3f50529869723184bfa7bb7933e89a7f" + "sha2": "e0ae09c0a24fbf452fa08f5c08208846c7df9ce2" } ,{ "testCaseDescription": "javascript-for-of-statement-delete-test", @@ -389,9 +389,9 @@ "filePaths": [ "for-of-statement.js" ], - "sha1": "202a08ba3f50529869723184bfa7bb7933e89a7f", + "sha1": "e0ae09c0a24fbf452fa08f5c08208846c7df9ce2", "gitDir": "test/corpus/repos/javascript", - "sha2": "4a44d4b00382cfb3765b33274aeae1ca79d482f2" + "sha2": "ed738907075661e8ce229daa60e004c416a5ddf2" } ,{ "testCaseDescription": "javascript-for-of-statement-delete-rest-test", @@ -422,7 +422,7 @@ "filePaths": [ "for-of-statement.js" ], - "sha1": "4a44d4b00382cfb3765b33274aeae1ca79d482f2", + "sha1": "ed738907075661e8ce229daa60e004c416a5ddf2", "gitDir": "test/corpus/repos/javascript", - "sha2": "1cbcc1b45ee2afdae4047efbc3ee0f15e89e3394" + "sha2": "536e58f01a1c35bfed654e16dc15d4b2636913b7" }] diff --git a/test/corpus/diff-summaries/javascript/for-statement.json b/test/corpus/diff-summaries/javascript/for-statement.json index d91369f95..641bada7e 100644 --- a/test/corpus/diff-summaries/javascript/for-statement.json +++ b/test/corpus/diff-summaries/javascript/for-statement.json @@ -27,9 +27,9 @@ "filePaths": [ "for-statement.js" ], - "sha1": "af26873a60eeb28bb292941d2ee8cae7449c9a37", + "sha1": "0f63f399f084244c4cfcd918876a8c5e659e8ade", "gitDir": "test/corpus/repos/javascript", - "sha2": "4665224dffa93b74a2f0a8053558dfb93b45af47" + "sha2": "7099da096426789e903a008322119184fe353667" } ,{ "testCaseDescription": "javascript-for-statement-replacement-insert-test", @@ -77,9 +77,9 @@ "filePaths": [ "for-statement.js" ], - "sha1": "4665224dffa93b74a2f0a8053558dfb93b45af47", + "sha1": "7099da096426789e903a008322119184fe353667", "gitDir": "test/corpus/repos/javascript", - "sha2": "538dc4c01c536388c10e1815483666e3af597c91" + "sha2": "74f2e9af36fcd6da27f51ac28ae448b4265bbc35" } ,{ "testCaseDescription": "javascript-for-statement-delete-insert-test", @@ -123,9 +123,9 @@ "filePaths": [ "for-statement.js" ], - "sha1": "538dc4c01c536388c10e1815483666e3af597c91", + "sha1": "74f2e9af36fcd6da27f51ac28ae448b4265bbc35", "gitDir": "test/corpus/repos/javascript", - "sha2": "5391123a87a501fa3ee089ba964b2944bdb19cd4" + "sha2": "b01d035ff217d4670f859865b248f6d076181288" } ,{ "testCaseDescription": "javascript-for-statement-replacement-test", @@ -169,9 +169,9 @@ "filePaths": [ "for-statement.js" ], - "sha1": "5391123a87a501fa3ee089ba964b2944bdb19cd4", + "sha1": "b01d035ff217d4670f859865b248f6d076181288", "gitDir": "test/corpus/repos/javascript", - "sha2": "df2bb1dc7f724576ce006be7fd2faac784a6ee04" + "sha2": "8182996a9a072de805b19ceb80bc6d39d8693537" } ,{ "testCaseDescription": "javascript-for-statement-delete-replacement-test", @@ -236,9 +236,9 @@ "filePaths": [ "for-statement.js" ], - "sha1": "df2bb1dc7f724576ce006be7fd2faac784a6ee04", + "sha1": "8182996a9a072de805b19ceb80bc6d39d8693537", "gitDir": "test/corpus/repos/javascript", - "sha2": "a244106eee60395f9ffbd4a8ae799ed2df4529bf" + "sha2": "9f53049277b37934e3a5cdeb842cc1eb2db27042" } ,{ "testCaseDescription": "javascript-for-statement-delete-test", @@ -269,9 +269,9 @@ "filePaths": [ "for-statement.js" ], - "sha1": "a244106eee60395f9ffbd4a8ae799ed2df4529bf", + "sha1": "9f53049277b37934e3a5cdeb842cc1eb2db27042", "gitDir": "test/corpus/repos/javascript", - "sha2": "405664414cbd68bbe5ffa0c689fa30cc234c289f" + "sha2": "592a641594a1bed9a74e1a439ca9c437cd99e2c0" } ,{ "testCaseDescription": "javascript-for-statement-delete-rest-test", @@ -302,7 +302,7 @@ "filePaths": [ "for-statement.js" ], - "sha1": "405664414cbd68bbe5ffa0c689fa30cc234c289f", + "sha1": "592a641594a1bed9a74e1a439ca9c437cd99e2c0", "gitDir": "test/corpus/repos/javascript", - "sha2": "5c8734b51a5ad1b14629d6ba40597bcb713ffab0" + "sha2": "7c328351e5e8debb38b46a45f43481581e438666" }] diff --git a/test/corpus/diff-summaries/javascript/function-call-args.json b/test/corpus/diff-summaries/javascript/function-call-args.json index 953f6afeb..4c3a4aa85 100644 --- a/test/corpus/diff-summaries/javascript/function-call-args.json +++ b/test/corpus/diff-summaries/javascript/function-call-args.json @@ -27,9 +27,9 @@ "filePaths": [ "function-call-args.js" ], - "sha1": "c64bd8c8fddd5dfddd8b66e5da73f44196a2f949", + "sha1": "90687f3994b4645e5db5b97ec4da3502fbe9053d", "gitDir": "test/corpus/repos/javascript", - "sha2": "28d158494212d7e7a8d669cfcf00cb94c469fd8a" + "sha2": "aaad24da26976a73c6d19f8663d8b1643c4465b5" } ,{ "testCaseDescription": "javascript-function-call-args-replacement-insert-test", @@ -77,9 +77,9 @@ "filePaths": [ "function-call-args.js" ], - "sha1": "28d158494212d7e7a8d669cfcf00cb94c469fd8a", + "sha1": "aaad24da26976a73c6d19f8663d8b1643c4465b5", "gitDir": "test/corpus/repos/javascript", - "sha2": "fd6089792e1161e4e8250c20c114f484007c2198" + "sha2": "d461ca4c5b99ac714342ba5a97a8b19822abf355" } ,{ "testCaseDescription": "javascript-function-call-args-delete-insert-test", @@ -273,9 +273,9 @@ "filePaths": [ "function-call-args.js" ], - "sha1": "fd6089792e1161e4e8250c20c114f484007c2198", + "sha1": "d461ca4c5b99ac714342ba5a97a8b19822abf355", "gitDir": "test/corpus/repos/javascript", - "sha2": "692db1304b7df4f8705b40d6c6db5a223ae748c1" + "sha2": "5f1e05fcea9ea246eced001a88fb7872c1ae5923" } ,{ "testCaseDescription": "javascript-function-call-args-replacement-test", @@ -469,9 +469,9 @@ "filePaths": [ "function-call-args.js" ], - "sha1": "692db1304b7df4f8705b40d6c6db5a223ae748c1", + "sha1": "5f1e05fcea9ea246eced001a88fb7872c1ae5923", "gitDir": "test/corpus/repos/javascript", - "sha2": "292a4c61772ea003e3c6871c38b32609872890a6" + "sha2": "ec8b293cdef0a7d4fce7791690c010b170e64c87" } ,{ "testCaseDescription": "javascript-function-call-args-delete-replacement-test", @@ -536,9 +536,9 @@ "filePaths": [ "function-call-args.js" ], - "sha1": "292a4c61772ea003e3c6871c38b32609872890a6", + "sha1": "ec8b293cdef0a7d4fce7791690c010b170e64c87", "gitDir": "test/corpus/repos/javascript", - "sha2": "83b196b17789937e6cd4cabc48a69f3b695da404" + "sha2": "36858f5bcf436b803282fedf78c4c997ce3562a7" } ,{ "testCaseDescription": "javascript-function-call-args-delete-test", @@ -569,9 +569,9 @@ "filePaths": [ "function-call-args.js" ], - "sha1": "83b196b17789937e6cd4cabc48a69f3b695da404", + "sha1": "36858f5bcf436b803282fedf78c4c997ce3562a7", "gitDir": "test/corpus/repos/javascript", - "sha2": "5152aeeee214a3ccf900f0ac3db753f8d515e6eb" + "sha2": "d31e105c5f3e4c14ac404da8d6ee605cebd47126" } ,{ "testCaseDescription": "javascript-function-call-args-delete-rest-test", @@ -602,7 +602,7 @@ "filePaths": [ "function-call-args.js" ], - "sha1": "5152aeeee214a3ccf900f0ac3db753f8d515e6eb", + "sha1": "d31e105c5f3e4c14ac404da8d6ee605cebd47126", "gitDir": "test/corpus/repos/javascript", - "sha2": "2ad39701c647bc8063509309d3cc04d0c6adf0e8" + "sha2": "f110a993d59a58f31e4b09bd46734026c4fdcc60" }] diff --git a/test/corpus/diff-summaries/javascript/function-call.json b/test/corpus/diff-summaries/javascript/function-call.json index 26803fb1e..b4c808d74 100644 --- a/test/corpus/diff-summaries/javascript/function-call.json +++ b/test/corpus/diff-summaries/javascript/function-call.json @@ -27,9 +27,9 @@ "filePaths": [ "function-call.js" ], - "sha1": "69d03ecd07566e6fa325c378815462768d32a996", + "sha1": "bd29fccbe38961789cd724a6537993e68f491091", "gitDir": "test/corpus/repos/javascript", - "sha2": "5c33dfd9f5a31344ff92b13b536fab395123631f" + "sha2": "8f45c8caf64bcf2ecc371c0c865d25de1965ca81" } ,{ "testCaseDescription": "javascript-function-call-replacement-insert-test", @@ -77,9 +77,9 @@ "filePaths": [ "function-call.js" ], - "sha1": "5c33dfd9f5a31344ff92b13b536fab395123631f", + "sha1": "8f45c8caf64bcf2ecc371c0c865d25de1965ca81", "gitDir": "test/corpus/repos/javascript", - "sha2": "9b2feff82b5b2dcd66fe5eaf3370f60d301ae00f" + "sha2": "3c90d6519f2134b74fb9393f42d42476d101b75a" } ,{ "testCaseDescription": "javascript-function-call-delete-insert-test", @@ -123,9 +123,9 @@ "filePaths": [ "function-call.js" ], - "sha1": "9b2feff82b5b2dcd66fe5eaf3370f60d301ae00f", + "sha1": "3c90d6519f2134b74fb9393f42d42476d101b75a", "gitDir": "test/corpus/repos/javascript", - "sha2": "01de50c44273a20e735f5e0befe65f6373aa2edb" + "sha2": "92c66af1fe0ad64050da91f4bad6b40fc8690614" } ,{ "testCaseDescription": "javascript-function-call-replacement-test", @@ -169,9 +169,9 @@ "filePaths": [ "function-call.js" ], - "sha1": "01de50c44273a20e735f5e0befe65f6373aa2edb", + "sha1": "92c66af1fe0ad64050da91f4bad6b40fc8690614", "gitDir": "test/corpus/repos/javascript", - "sha2": "bcb608a5b2e2c4e887e85005f873cc884aa8aee9" + "sha2": "23b31eae7b695b2ec4f2bb2e5d66746215dd718e" } ,{ "testCaseDescription": "javascript-function-call-delete-replacement-test", @@ -236,9 +236,9 @@ "filePaths": [ "function-call.js" ], - "sha1": "bcb608a5b2e2c4e887e85005f873cc884aa8aee9", + "sha1": "23b31eae7b695b2ec4f2bb2e5d66746215dd718e", "gitDir": "test/corpus/repos/javascript", - "sha2": "a8fadba8690bd1195a9d0868aa57bd19e2ee7af6" + "sha2": "050239bb60162d04425370eb4efa229b7fb6b8f5" } ,{ "testCaseDescription": "javascript-function-call-delete-test", @@ -269,9 +269,9 @@ "filePaths": [ "function-call.js" ], - "sha1": "a8fadba8690bd1195a9d0868aa57bd19e2ee7af6", + "sha1": "050239bb60162d04425370eb4efa229b7fb6b8f5", "gitDir": "test/corpus/repos/javascript", - "sha2": "059865b81c068f73f9ccdc584d6e9eba10a4e3c7" + "sha2": "14b6c7a0fc4a775c9915ccbf0a9082b5a0566e01" } ,{ "testCaseDescription": "javascript-function-call-delete-rest-test", @@ -302,7 +302,7 @@ "filePaths": [ "function-call.js" ], - "sha1": "059865b81c068f73f9ccdc584d6e9eba10a4e3c7", + "sha1": "14b6c7a0fc4a775c9915ccbf0a9082b5a0566e01", "gitDir": "test/corpus/repos/javascript", - "sha2": "24037753ea53b15094b5e71eef37b694a5f001fe" + "sha2": "1eac526dd11d55220946d9b6306e3031c11e73a7" }] diff --git a/test/corpus/diff-summaries/javascript/function.json b/test/corpus/diff-summaries/javascript/function.json index 6f2d1f987..e855ec70e 100644 --- a/test/corpus/diff-summaries/javascript/function.json +++ b/test/corpus/diff-summaries/javascript/function.json @@ -27,9 +27,9 @@ "filePaths": [ "function.js" ], - "sha1": "294584bae27cd565886c9c1064c423ab7a04e42d", + "sha1": "0921c7be9afb30bdf6fa3861d12c20a87ae67736", "gitDir": "test/corpus/repos/javascript", - "sha2": "35fb01b172ebb75cea231977f4846d85dcca0518" + "sha2": "c14206873e94c5b71dcaef2a68cc885f9fe02438" } ,{ "testCaseDescription": "javascript-function-replacement-insert-test", @@ -77,9 +77,9 @@ "filePaths": [ "function.js" ], - "sha1": "35fb01b172ebb75cea231977f4846d85dcca0518", + "sha1": "c14206873e94c5b71dcaef2a68cc885f9fe02438", "gitDir": "test/corpus/repos/javascript", - "sha2": "d5d65c1b1c15e480ebae432562f6041c5145751b" + "sha2": "be57190fb1f51d913dfeb73c34d00dc57fcb1872" } ,{ "testCaseDescription": "javascript-function-delete-insert-test", @@ -123,9 +123,9 @@ "filePaths": [ "function.js" ], - "sha1": "d5d65c1b1c15e480ebae432562f6041c5145751b", + "sha1": "be57190fb1f51d913dfeb73c34d00dc57fcb1872", "gitDir": "test/corpus/repos/javascript", - "sha2": "c9e5e8d1bd883377d9848dac828e1b64053731ad" + "sha2": "fbadfc3fbbde8967568595bb4675ddc476126daf" } ,{ "testCaseDescription": "javascript-function-replacement-test", @@ -169,9 +169,9 @@ "filePaths": [ "function.js" ], - "sha1": "c9e5e8d1bd883377d9848dac828e1b64053731ad", + "sha1": "fbadfc3fbbde8967568595bb4675ddc476126daf", "gitDir": "test/corpus/repos/javascript", - "sha2": "4bca807563e9c52adbaaa810452422fd0bb48d73" + "sha2": "57f9bf7c0a45a4f94d567465b6b977343d32f50b" } ,{ "testCaseDescription": "javascript-function-delete-replacement-test", @@ -236,9 +236,9 @@ "filePaths": [ "function.js" ], - "sha1": "4bca807563e9c52adbaaa810452422fd0bb48d73", + "sha1": "57f9bf7c0a45a4f94d567465b6b977343d32f50b", "gitDir": "test/corpus/repos/javascript", - "sha2": "32efff192345ba630c43bbac21d4b63ae582b70a" + "sha2": "d35302be0f16f464cc4d0097a751e65d00abc9a1" } ,{ "testCaseDescription": "javascript-function-delete-test", @@ -269,9 +269,9 @@ "filePaths": [ "function.js" ], - "sha1": "32efff192345ba630c43bbac21d4b63ae582b70a", + "sha1": "d35302be0f16f464cc4d0097a751e65d00abc9a1", "gitDir": "test/corpus/repos/javascript", - "sha2": "f76ff63edcf9f3daccae98ca8db54e3f4ef693c9" + "sha2": "0e0a3468af5fc91169f996a1334b146594d1e795" } ,{ "testCaseDescription": "javascript-function-delete-rest-test", @@ -302,7 +302,7 @@ "filePaths": [ "function.js" ], - "sha1": "f76ff63edcf9f3daccae98ca8db54e3f4ef693c9", + "sha1": "0e0a3468af5fc91169f996a1334b146594d1e795", "gitDir": "test/corpus/repos/javascript", - "sha2": "822aeb40bb7867ac30402c6f1af8dcea662ed4fb" + "sha2": "2327a0433e3123ddf19226ee5172c928f24b3af1" }] diff --git a/test/corpus/diff-summaries/javascript/generator-function.json b/test/corpus/diff-summaries/javascript/generator-function.json index 47540797d..63cf0b746 100644 --- a/test/corpus/diff-summaries/javascript/generator-function.json +++ b/test/corpus/diff-summaries/javascript/generator-function.json @@ -27,9 +27,9 @@ "filePaths": [ "generator-function.js" ], - "sha1": "016ccc9573eb5bfe5ec52dcd5bb58239755ca8fd", + "sha1": "dcaa57653ecd13d885de551a47032d37ef10e47e", "gitDir": "test/corpus/repos/javascript", - "sha2": "9a733ddbec9f01fe6f4ca2fa486f2de0c530103c" + "sha2": "69b059e9e82e91d554c61235b348c86fc8848d37" } ,{ "testCaseDescription": "javascript-generator-function-replacement-insert-test", @@ -77,9 +77,9 @@ "filePaths": [ "generator-function.js" ], - "sha1": "9a733ddbec9f01fe6f4ca2fa486f2de0c530103c", + "sha1": "69b059e9e82e91d554c61235b348c86fc8848d37", "gitDir": "test/corpus/repos/javascript", - "sha2": "05d9fda285817a720021accf27c5c43331f2730d" + "sha2": "8fc9682cd35f3ba8d4fd15f05651d0a917e755e8" } ,{ "testCaseDescription": "javascript-generator-function-delete-insert-test", @@ -123,9 +123,9 @@ "filePaths": [ "generator-function.js" ], - "sha1": "05d9fda285817a720021accf27c5c43331f2730d", + "sha1": "8fc9682cd35f3ba8d4fd15f05651d0a917e755e8", "gitDir": "test/corpus/repos/javascript", - "sha2": "fc061ab1b2ab235efb00c4f75b5a26c7d9840e8a" + "sha2": "25bc36bf665a0aff1a83ab961fe4611121a16e2e" } ,{ "testCaseDescription": "javascript-generator-function-replacement-test", @@ -169,9 +169,9 @@ "filePaths": [ "generator-function.js" ], - "sha1": "fc061ab1b2ab235efb00c4f75b5a26c7d9840e8a", + "sha1": "25bc36bf665a0aff1a83ab961fe4611121a16e2e", "gitDir": "test/corpus/repos/javascript", - "sha2": "e07858b1726d3d1fb57abb417cb27b06a81b54dd" + "sha2": "1502425cb39a05b219e064e5e5b39a9be6beb18e" } ,{ "testCaseDescription": "javascript-generator-function-delete-replacement-test", @@ -236,9 +236,9 @@ "filePaths": [ "generator-function.js" ], - "sha1": "e07858b1726d3d1fb57abb417cb27b06a81b54dd", + "sha1": "1502425cb39a05b219e064e5e5b39a9be6beb18e", "gitDir": "test/corpus/repos/javascript", - "sha2": "47daeff4491811210cb35ead5a5d0d3a4503f4b5" + "sha2": "0d9d44b51dbb7c8bd0a0e451bf1fb2a8540d8add" } ,{ "testCaseDescription": "javascript-generator-function-delete-test", @@ -269,9 +269,9 @@ "filePaths": [ "generator-function.js" ], - "sha1": "47daeff4491811210cb35ead5a5d0d3a4503f4b5", + "sha1": "0d9d44b51dbb7c8bd0a0e451bf1fb2a8540d8add", "gitDir": "test/corpus/repos/javascript", - "sha2": "6e64f5e58a3df217aefde820e66413fa8e486d6d" + "sha2": "4d4d00350fd9e0ccfc94de3844bd3fee97b7de58" } ,{ "testCaseDescription": "javascript-generator-function-delete-rest-test", @@ -302,7 +302,7 @@ "filePaths": [ "generator-function.js" ], - "sha1": "6e64f5e58a3df217aefde820e66413fa8e486d6d", + "sha1": "4d4d00350fd9e0ccfc94de3844bd3fee97b7de58", "gitDir": "test/corpus/repos/javascript", - "sha2": "13ebce1d1e86a542435c13c42f189fc5f63ffa80" + "sha2": "2757c3a3cfdea7d078af6cd6c05b4355fff8b112" }] diff --git a/test/corpus/diff-summaries/javascript/identifier.json b/test/corpus/diff-summaries/javascript/identifier.json index eff69358a..18fff2a97 100644 --- a/test/corpus/diff-summaries/javascript/identifier.json +++ b/test/corpus/diff-summaries/javascript/identifier.json @@ -27,9 +27,9 @@ "filePaths": [ "identifier.js" ], - "sha1": "e8164f9a5c7441db5367d1dee13694204e67e3ab", + "sha1": "ea0156c09a6d9c183d037bddda50ce815c00548f", "gitDir": "test/corpus/repos/javascript", - "sha2": "75e27ff4b3c70434eef42d3170bdb9c7a2a60c28" + "sha2": "e9c20e9a3247f9c4301b51c97c0e9ebe1d4d34be" } ,{ "testCaseDescription": "javascript-identifier-replacement-insert-test", @@ -77,9 +77,9 @@ "filePaths": [ "identifier.js" ], - "sha1": "75e27ff4b3c70434eef42d3170bdb9c7a2a60c28", + "sha1": "e9c20e9a3247f9c4301b51c97c0e9ebe1d4d34be", "gitDir": "test/corpus/repos/javascript", - "sha2": "509a9a37149c0bd5c34b27441ca3ba82bd52dda5" + "sha2": "bd8e182b45f051c7314f54de7f22423d36767b0a" } ,{ "testCaseDescription": "javascript-identifier-delete-insert-test", @@ -123,9 +123,9 @@ "filePaths": [ "identifier.js" ], - "sha1": "509a9a37149c0bd5c34b27441ca3ba82bd52dda5", + "sha1": "bd8e182b45f051c7314f54de7f22423d36767b0a", "gitDir": "test/corpus/repos/javascript", - "sha2": "2be41e7a7f6e3a2785ef78f40060a416a23d781b" + "sha2": "03d5aee6333ae73bb1c9cfc6671d5520601ef290" } ,{ "testCaseDescription": "javascript-identifier-replacement-test", @@ -169,9 +169,9 @@ "filePaths": [ "identifier.js" ], - "sha1": "2be41e7a7f6e3a2785ef78f40060a416a23d781b", + "sha1": "03d5aee6333ae73bb1c9cfc6671d5520601ef290", "gitDir": "test/corpus/repos/javascript", - "sha2": "6f0f8d55da8aa3a8296d008487484829f7d2bf3a" + "sha2": "ddfc882641f80549771567151156aa80b4a6d443" } ,{ "testCaseDescription": "javascript-identifier-delete-replacement-test", @@ -236,9 +236,9 @@ "filePaths": [ "identifier.js" ], - "sha1": "6f0f8d55da8aa3a8296d008487484829f7d2bf3a", + "sha1": "ddfc882641f80549771567151156aa80b4a6d443", "gitDir": "test/corpus/repos/javascript", - "sha2": "b7213ebdf5760f71f68072eefbe4e96553daef8c" + "sha2": "9a8d227c90fea676142f53a5d98aa4fe54ea15f2" } ,{ "testCaseDescription": "javascript-identifier-delete-test", @@ -269,9 +269,9 @@ "filePaths": [ "identifier.js" ], - "sha1": "b7213ebdf5760f71f68072eefbe4e96553daef8c", + "sha1": "9a8d227c90fea676142f53a5d98aa4fe54ea15f2", "gitDir": "test/corpus/repos/javascript", - "sha2": "83da588f6151bb142adfe665a6b24c76d754571c" + "sha2": "154521e82253448dfe113e5bd2fdb8f5d72fc002" } ,{ "testCaseDescription": "javascript-identifier-delete-rest-test", @@ -302,7 +302,7 @@ "filePaths": [ "identifier.js" ], - "sha1": "83da588f6151bb142adfe665a6b24c76d754571c", + "sha1": "154521e82253448dfe113e5bd2fdb8f5d72fc002", "gitDir": "test/corpus/repos/javascript", - "sha2": "bd9d0d22b6a226d63e44c3d654b6b618571f9912" + "sha2": "562fd7786138fba4253581a1f2995c02007f74b9" }] diff --git a/test/corpus/diff-summaries/javascript/if-else.json b/test/corpus/diff-summaries/javascript/if-else.json index a09c40fd0..d314e7c11 100644 --- a/test/corpus/diff-summaries/javascript/if-else.json +++ b/test/corpus/diff-summaries/javascript/if-else.json @@ -27,9 +27,9 @@ "filePaths": [ "if-else.js" ], - "sha1": "82dd9b63b3f990900cef36bee489fcaacf288d02", + "sha1": "c9021762fc3f372be0d71362df586edc1e74f4d0", "gitDir": "test/corpus/repos/javascript", - "sha2": "37d6c28a2511afe06f6f8a56a347e53a02de2dc9" + "sha2": "4670ff79891fe66aef3f92c207b6b93a6b13dd20" } ,{ "testCaseDescription": "javascript-if-else-replacement-insert-test", @@ -77,9 +77,9 @@ "filePaths": [ "if-else.js" ], - "sha1": "37d6c28a2511afe06f6f8a56a347e53a02de2dc9", + "sha1": "4670ff79891fe66aef3f92c207b6b93a6b13dd20", "gitDir": "test/corpus/repos/javascript", - "sha2": "10d61c3c421fb02ba22b54ff983cd29459654d24" + "sha2": "e47e54e15d63f3d9b67d2fe4bfd9e9d9b98f83de" } ,{ "testCaseDescription": "javascript-if-else-delete-insert-test", @@ -123,9 +123,9 @@ "filePaths": [ "if-else.js" ], - "sha1": "10d61c3c421fb02ba22b54ff983cd29459654d24", + "sha1": "e47e54e15d63f3d9b67d2fe4bfd9e9d9b98f83de", "gitDir": "test/corpus/repos/javascript", - "sha2": "3440c419be8b2ae978d25f259cad4815e07ab89d" + "sha2": "ff71eaad0cda4ae6e40a1ace67c8e8855129f297" } ,{ "testCaseDescription": "javascript-if-else-replacement-test", @@ -169,9 +169,9 @@ "filePaths": [ "if-else.js" ], - "sha1": "3440c419be8b2ae978d25f259cad4815e07ab89d", + "sha1": "ff71eaad0cda4ae6e40a1ace67c8e8855129f297", "gitDir": "test/corpus/repos/javascript", - "sha2": "1e79f5288c355ba9a3f06f3ec6e7cdf73526487e" + "sha2": "f73d3a5494c68a92758265e047ce766571786700" } ,{ "testCaseDescription": "javascript-if-else-delete-replacement-test", @@ -236,9 +236,9 @@ "filePaths": [ "if-else.js" ], - "sha1": "1e79f5288c355ba9a3f06f3ec6e7cdf73526487e", + "sha1": "f73d3a5494c68a92758265e047ce766571786700", "gitDir": "test/corpus/repos/javascript", - "sha2": "edc8dd3ebd0490925aed9cb346cde3ab0abe732e" + "sha2": "5e1fd2dc43887977b5ca0c6fce1e12fcbdc46882" } ,{ "testCaseDescription": "javascript-if-else-delete-test", @@ -269,9 +269,9 @@ "filePaths": [ "if-else.js" ], - "sha1": "edc8dd3ebd0490925aed9cb346cde3ab0abe732e", + "sha1": "5e1fd2dc43887977b5ca0c6fce1e12fcbdc46882", "gitDir": "test/corpus/repos/javascript", - "sha2": "8a074903d8c3de5e7aa705d257ffd2f00ce3d318" + "sha2": "249e0e5a68af8672af85b0a064593d5840ef11c7" } ,{ "testCaseDescription": "javascript-if-else-delete-rest-test", @@ -302,7 +302,7 @@ "filePaths": [ "if-else.js" ], - "sha1": "8a074903d8c3de5e7aa705d257ffd2f00ce3d318", + "sha1": "249e0e5a68af8672af85b0a064593d5840ef11c7", "gitDir": "test/corpus/repos/javascript", - "sha2": "b68fd6fad9ad8bbfb5fef0b97e42bb9899f01a0e" + "sha2": "b2046cbd2baf7870677913d1acc35696f7a97f84" }] diff --git a/test/corpus/diff-summaries/javascript/if.json b/test/corpus/diff-summaries/javascript/if.json index 4c4e6f770..ed450b2d0 100644 --- a/test/corpus/diff-summaries/javascript/if.json +++ b/test/corpus/diff-summaries/javascript/if.json @@ -27,9 +27,9 @@ "filePaths": [ "if.js" ], - "sha1": "b8ad05d0253ae191a5f160e7048edd003cbfd266", + "sha1": "88eddedb2d7666ebcc74cb1693e7f24e13e4e481", "gitDir": "test/corpus/repos/javascript", - "sha2": "af68a65130c39064b6b6ff086c83bb15a93c09df" + "sha2": "398030c49850abab6e773e4222952743bbd35619" } ,{ "testCaseDescription": "javascript-if-replacement-insert-test", @@ -77,9 +77,9 @@ "filePaths": [ "if.js" ], - "sha1": "af68a65130c39064b6b6ff086c83bb15a93c09df", + "sha1": "398030c49850abab6e773e4222952743bbd35619", "gitDir": "test/corpus/repos/javascript", - "sha2": "ca0d3248805ea9e4a6db03283753386c1add674c" + "sha2": "a5b0e3a01683c3273038baed42d8cb553f076528" } ,{ "testCaseDescription": "javascript-if-delete-insert-test", @@ -123,9 +123,9 @@ "filePaths": [ "if.js" ], - "sha1": "ca0d3248805ea9e4a6db03283753386c1add674c", + "sha1": "a5b0e3a01683c3273038baed42d8cb553f076528", "gitDir": "test/corpus/repos/javascript", - "sha2": "4449122ca03d44093b55013864f0b91ad89b34c5" + "sha2": "f6e410f5c881a7706564be66e6e0c346b1c83319" } ,{ "testCaseDescription": "javascript-if-replacement-test", @@ -169,9 +169,9 @@ "filePaths": [ "if.js" ], - "sha1": "4449122ca03d44093b55013864f0b91ad89b34c5", + "sha1": "f6e410f5c881a7706564be66e6e0c346b1c83319", "gitDir": "test/corpus/repos/javascript", - "sha2": "fb678c888f2ab154619dc7b066c706fc38b3b1e6" + "sha2": "e4e027e6a7c794c693011b35ef5e7d7e0129d4d2" } ,{ "testCaseDescription": "javascript-if-delete-replacement-test", @@ -236,9 +236,9 @@ "filePaths": [ "if.js" ], - "sha1": "fb678c888f2ab154619dc7b066c706fc38b3b1e6", + "sha1": "e4e027e6a7c794c693011b35ef5e7d7e0129d4d2", "gitDir": "test/corpus/repos/javascript", - "sha2": "d7133bfd9d74d7aa507fdf0eef61ed38aac6e292" + "sha2": "d74f4b903c9888429dd3d8d8d604bac231caa3f2" } ,{ "testCaseDescription": "javascript-if-delete-test", @@ -269,9 +269,9 @@ "filePaths": [ "if.js" ], - "sha1": "d7133bfd9d74d7aa507fdf0eef61ed38aac6e292", + "sha1": "d74f4b903c9888429dd3d8d8d604bac231caa3f2", "gitDir": "test/corpus/repos/javascript", - "sha2": "d46b553e4344fd4372f71aabf2b3c4592a314ee7" + "sha2": "37d76cba66fa561e813c9c7b38b8e3b0edf0be20" } ,{ "testCaseDescription": "javascript-if-delete-rest-test", @@ -302,7 +302,7 @@ "filePaths": [ "if.js" ], - "sha1": "d46b553e4344fd4372f71aabf2b3c4592a314ee7", + "sha1": "37d76cba66fa561e813c9c7b38b8e3b0edf0be20", "gitDir": "test/corpus/repos/javascript", - "sha2": "82dd9b63b3f990900cef36bee489fcaacf288d02" + "sha2": "c9021762fc3f372be0d71362df586edc1e74f4d0" }] diff --git a/test/corpus/diff-summaries/javascript/math-assignment-operator.json b/test/corpus/diff-summaries/javascript/math-assignment-operator.json index c99252887..c85ce3a0d 100644 --- a/test/corpus/diff-summaries/javascript/math-assignment-operator.json +++ b/test/corpus/diff-summaries/javascript/math-assignment-operator.json @@ -27,9 +27,9 @@ "filePaths": [ "math-assignment-operator.js" ], - "sha1": "7a5a7e14fdfb56a4dae67672a83aceb49d90f6bf", + "sha1": "5fc82ac3374f4c8d50af76e2ae299a59e4cff396", "gitDir": "test/corpus/repos/javascript", - "sha2": "2aed63ce1b4af89d4d78887777822aa729dc46ba" + "sha2": "c1179440cd79faa8f00d6b50c8f99b6f4fa3b2c7" } ,{ "testCaseDescription": "javascript-math-assignment-operator-replacement-insert-test", @@ -77,9 +77,9 @@ "filePaths": [ "math-assignment-operator.js" ], - "sha1": "2aed63ce1b4af89d4d78887777822aa729dc46ba", + "sha1": "c1179440cd79faa8f00d6b50c8f99b6f4fa3b2c7", "gitDir": "test/corpus/repos/javascript", - "sha2": "9d231bac8540a68b2ea8d7df89c0cff4e1250a4b" + "sha2": "9f90dacee15220d6d61f1d9d221980c7c793c7a3" } ,{ "testCaseDescription": "javascript-math-assignment-operator-delete-insert-test", @@ -123,9 +123,9 @@ "filePaths": [ "math-assignment-operator.js" ], - "sha1": "9d231bac8540a68b2ea8d7df89c0cff4e1250a4b", + "sha1": "9f90dacee15220d6d61f1d9d221980c7c793c7a3", "gitDir": "test/corpus/repos/javascript", - "sha2": "4b0f35714cd2b735d9228b7ecc82d9d8af8a5367" + "sha2": "390eb2aa1f63abbaae7f33139e1db4ec60ddb736" } ,{ "testCaseDescription": "javascript-math-assignment-operator-replacement-test", @@ -169,9 +169,9 @@ "filePaths": [ "math-assignment-operator.js" ], - "sha1": "4b0f35714cd2b735d9228b7ecc82d9d8af8a5367", + "sha1": "390eb2aa1f63abbaae7f33139e1db4ec60ddb736", "gitDir": "test/corpus/repos/javascript", - "sha2": "b1dbceca404978015a90e1dce406759980e0dbc0" + "sha2": "7b6eff26944c44962cecfb8b041a006fc4d5cff4" } ,{ "testCaseDescription": "javascript-math-assignment-operator-delete-replacement-test", @@ -236,9 +236,9 @@ "filePaths": [ "math-assignment-operator.js" ], - "sha1": "b1dbceca404978015a90e1dce406759980e0dbc0", + "sha1": "7b6eff26944c44962cecfb8b041a006fc4d5cff4", "gitDir": "test/corpus/repos/javascript", - "sha2": "913db4af5c664dfbe4523f49d2fa8943022a43f8" + "sha2": "35b4ffd0eeafbae6113ad22b86a1d278f5ed26a8" } ,{ "testCaseDescription": "javascript-math-assignment-operator-delete-test", @@ -269,9 +269,9 @@ "filePaths": [ "math-assignment-operator.js" ], - "sha1": "913db4af5c664dfbe4523f49d2fa8943022a43f8", + "sha1": "35b4ffd0eeafbae6113ad22b86a1d278f5ed26a8", "gitDir": "test/corpus/repos/javascript", - "sha2": "aa754293f0b9582f1efc6990001c9706c8d1d744" + "sha2": "411c2e22bb0eccdeb3d32fdc588e9e1a92ac4442" } ,{ "testCaseDescription": "javascript-math-assignment-operator-delete-rest-test", @@ -302,7 +302,7 @@ "filePaths": [ "math-assignment-operator.js" ], - "sha1": "aa754293f0b9582f1efc6990001c9706c8d1d744", + "sha1": "411c2e22bb0eccdeb3d32fdc588e9e1a92ac4442", "gitDir": "test/corpus/repos/javascript", - "sha2": "195a1d9a04af2cce44e8af09913140e80af6656f" + "sha2": "b0363eb07d0284130aab04183573dcd31fa7f221" }] diff --git a/test/corpus/diff-summaries/javascript/math-operator.json b/test/corpus/diff-summaries/javascript/math-operator.json index 65fa0700a..dc0dbcc01 100644 --- a/test/corpus/diff-summaries/javascript/math-operator.json +++ b/test/corpus/diff-summaries/javascript/math-operator.json @@ -27,9 +27,9 @@ "filePaths": [ "math-operator.js" ], - "sha1": "ebf93ce214fd99b995fc859da2c899eaf98b003a", + "sha1": "952d18ccd1d4413a1252458befbb6593253aa794", "gitDir": "test/corpus/repos/javascript", - "sha2": "93f7482ed81a2888cd6137a6015ed46fa12ceb2d" + "sha2": "0f5f7cf116643cca9937c190200836a873710883" } ,{ "testCaseDescription": "javascript-math-operator-replacement-insert-test", @@ -77,9 +77,9 @@ "filePaths": [ "math-operator.js" ], - "sha1": "93f7482ed81a2888cd6137a6015ed46fa12ceb2d", + "sha1": "0f5f7cf116643cca9937c190200836a873710883", "gitDir": "test/corpus/repos/javascript", - "sha2": "2b8502bbe9c10431c2a08133eb6180b1e27f537e" + "sha2": "1da37893a9e9441662973874ed47dd77654338fb" } ,{ "testCaseDescription": "javascript-math-operator-delete-insert-test", @@ -153,9 +153,9 @@ "filePaths": [ "math-operator.js" ], - "sha1": "2b8502bbe9c10431c2a08133eb6180b1e27f537e", + "sha1": "1da37893a9e9441662973874ed47dd77654338fb", "gitDir": "test/corpus/repos/javascript", - "sha2": "123e24693808106e6533b65a31e067441dd32d78" + "sha2": "aac275442430a4112052e502188bdc77cb31dc58" } ,{ "testCaseDescription": "javascript-math-operator-replacement-test", @@ -229,9 +229,9 @@ "filePaths": [ "math-operator.js" ], - "sha1": "123e24693808106e6533b65a31e067441dd32d78", + "sha1": "aac275442430a4112052e502188bdc77cb31dc58", "gitDir": "test/corpus/repos/javascript", - "sha2": "e44b221c2a7632162f4498cd54046476d74c39b7" + "sha2": "a42e5df3587157b8b86c4613a0460af6ac0d9477" } ,{ "testCaseDescription": "javascript-math-operator-delete-replacement-test", @@ -296,9 +296,9 @@ "filePaths": [ "math-operator.js" ], - "sha1": "e44b221c2a7632162f4498cd54046476d74c39b7", + "sha1": "a42e5df3587157b8b86c4613a0460af6ac0d9477", "gitDir": "test/corpus/repos/javascript", - "sha2": "12fc0e04bb901a3cd24aefbf530a5feaa7166195" + "sha2": "646e506df8f4ace3fda519ad69f21f13f34aa408" } ,{ "testCaseDescription": "javascript-math-operator-delete-test", @@ -329,9 +329,9 @@ "filePaths": [ "math-operator.js" ], - "sha1": "12fc0e04bb901a3cd24aefbf530a5feaa7166195", + "sha1": "646e506df8f4ace3fda519ad69f21f13f34aa408", "gitDir": "test/corpus/repos/javascript", - "sha2": "12b777458501d39cfc9bf6eb3a223fd942fd0ecb" + "sha2": "d261c59941740a794efd74dd3bd3e1b88df1d436" } ,{ "testCaseDescription": "javascript-math-operator-delete-rest-test", @@ -362,7 +362,7 @@ "filePaths": [ "math-operator.js" ], - "sha1": "12b777458501d39cfc9bf6eb3a223fd942fd0ecb", + "sha1": "d261c59941740a794efd74dd3bd3e1b88df1d436", "gitDir": "test/corpus/repos/javascript", - "sha2": "7e1caa9a941a609d09c734937d05d7b2414e8219" + "sha2": "4a00f98e1f34850ca8d14b8f33de4f8a0fcb7c40" }] diff --git a/test/corpus/diff-summaries/javascript/member-access-assignment.json b/test/corpus/diff-summaries/javascript/member-access-assignment.json index bf1d009fe..60d973914 100644 --- a/test/corpus/diff-summaries/javascript/member-access-assignment.json +++ b/test/corpus/diff-summaries/javascript/member-access-assignment.json @@ -27,9 +27,9 @@ "filePaths": [ "member-access-assignment.js" ], - "sha1": "5abf5273d87f2dd381fecb3cb1da4b3205c43884", + "sha1": "a4003ba4e78b0ae460decba084c34b15da1aa05e", "gitDir": "test/corpus/repos/javascript", - "sha2": "7c50ca76820e810821259114e73a62ee28d66b9f" + "sha2": "16101ac65aa3b3af782eafd2e4c93d307ab12a82" } ,{ "testCaseDescription": "javascript-member-access-assignment-replacement-insert-test", @@ -77,9 +77,9 @@ "filePaths": [ "member-access-assignment.js" ], - "sha1": "7c50ca76820e810821259114e73a62ee28d66b9f", + "sha1": "16101ac65aa3b3af782eafd2e4c93d307ab12a82", "gitDir": "test/corpus/repos/javascript", - "sha2": "97c06ba774b37bb505a9701e2c437da6a97ce086" + "sha2": "73e1be43e07e507caab17a550b53339b59b9ec70" } ,{ "testCaseDescription": "javascript-member-access-assignment-delete-insert-test", @@ -123,9 +123,9 @@ "filePaths": [ "member-access-assignment.js" ], - "sha1": "97c06ba774b37bb505a9701e2c437da6a97ce086", + "sha1": "73e1be43e07e507caab17a550b53339b59b9ec70", "gitDir": "test/corpus/repos/javascript", - "sha2": "0f6ba0959bef4f60fb13bed5524b7c743c4dbe32" + "sha2": "b3ddcbd42f82560f26d7223d64fb0a59b3f1fd6d" } ,{ "testCaseDescription": "javascript-member-access-assignment-replacement-test", @@ -169,9 +169,9 @@ "filePaths": [ "member-access-assignment.js" ], - "sha1": "0f6ba0959bef4f60fb13bed5524b7c743c4dbe32", + "sha1": "b3ddcbd42f82560f26d7223d64fb0a59b3f1fd6d", "gitDir": "test/corpus/repos/javascript", - "sha2": "833009a51368a08169ab7d8c7536fbd1b62c6d5b" + "sha2": "e8079105133dae2beea64e95d3b491cd3938d322" } ,{ "testCaseDescription": "javascript-member-access-assignment-delete-replacement-test", @@ -236,9 +236,9 @@ "filePaths": [ "member-access-assignment.js" ], - "sha1": "833009a51368a08169ab7d8c7536fbd1b62c6d5b", + "sha1": "e8079105133dae2beea64e95d3b491cd3938d322", "gitDir": "test/corpus/repos/javascript", - "sha2": "200d9b92ea3c25078e09984d93bd07a225175af4" + "sha2": "0205a7fb38a9a6d5b897e5b0e98c9a45c936e89d" } ,{ "testCaseDescription": "javascript-member-access-assignment-delete-test", @@ -269,9 +269,9 @@ "filePaths": [ "member-access-assignment.js" ], - "sha1": "200d9b92ea3c25078e09984d93bd07a225175af4", + "sha1": "0205a7fb38a9a6d5b897e5b0e98c9a45c936e89d", "gitDir": "test/corpus/repos/javascript", - "sha2": "ee587dae30db8fb647970f12f6777db23bbad620" + "sha2": "6c64da67067e3c0291791a301b469486afed28a2" } ,{ "testCaseDescription": "javascript-member-access-assignment-delete-rest-test", @@ -302,7 +302,7 @@ "filePaths": [ "member-access-assignment.js" ], - "sha1": "ee587dae30db8fb647970f12f6777db23bbad620", + "sha1": "6c64da67067e3c0291791a301b469486afed28a2", "gitDir": "test/corpus/repos/javascript", - "sha2": "e7314eba8beae9be9a34bcf91157e5e542f4b2a9" + "sha2": "1e25a73e1015c39932d3a621daa9081a4e46a9ba" }] diff --git a/test/corpus/diff-summaries/javascript/member-access.json b/test/corpus/diff-summaries/javascript/member-access.json index 8549b27c7..94f8abd02 100644 --- a/test/corpus/diff-summaries/javascript/member-access.json +++ b/test/corpus/diff-summaries/javascript/member-access.json @@ -27,9 +27,9 @@ "filePaths": [ "member-access.js" ], - "sha1": "2f07429c5135205d55550f4c64061a6ac987da17", + "sha1": "035ebadb21075a55367b83c380264365799ac421", "gitDir": "test/corpus/repos/javascript", - "sha2": "f88de966d0f942a55d170dbf43070e3cb3f26a3d" + "sha2": "f627d80f233c895dbe4c55592460fab353e58aab" } ,{ "testCaseDescription": "javascript-member-access-replacement-insert-test", @@ -77,9 +77,9 @@ "filePaths": [ "member-access.js" ], - "sha1": "f88de966d0f942a55d170dbf43070e3cb3f26a3d", + "sha1": "f627d80f233c895dbe4c55592460fab353e58aab", "gitDir": "test/corpus/repos/javascript", - "sha2": "6b63944a02141ea5f2696bac8c40dfb972883b13" + "sha2": "388603ce6932fd40cfee9bddaf18f3f407cf27a6" } ,{ "testCaseDescription": "javascript-member-access-delete-insert-test", @@ -123,9 +123,9 @@ "filePaths": [ "member-access.js" ], - "sha1": "6b63944a02141ea5f2696bac8c40dfb972883b13", + "sha1": "388603ce6932fd40cfee9bddaf18f3f407cf27a6", "gitDir": "test/corpus/repos/javascript", - "sha2": "46741210b901e8b9dfa87552c0adeddc7d6beab8" + "sha2": "fff56d1bd93eeee668ffeac7a30162fa7f81a91b" } ,{ "testCaseDescription": "javascript-member-access-replacement-test", @@ -169,9 +169,9 @@ "filePaths": [ "member-access.js" ], - "sha1": "46741210b901e8b9dfa87552c0adeddc7d6beab8", + "sha1": "fff56d1bd93eeee668ffeac7a30162fa7f81a91b", "gitDir": "test/corpus/repos/javascript", - "sha2": "2562b652ebd9aff9aae1acc1ac1b08610ef79f40" + "sha2": "6318121ceeab8d6e2f209d2eaa8476f5c416ebeb" } ,{ "testCaseDescription": "javascript-member-access-delete-replacement-test", @@ -236,9 +236,9 @@ "filePaths": [ "member-access.js" ], - "sha1": "2562b652ebd9aff9aae1acc1ac1b08610ef79f40", + "sha1": "6318121ceeab8d6e2f209d2eaa8476f5c416ebeb", "gitDir": "test/corpus/repos/javascript", - "sha2": "191e1b5188f0e9f15bd1ba61e6e608cc27bcf423" + "sha2": "90c11d04be5443162bc497267825252d029a3343" } ,{ "testCaseDescription": "javascript-member-access-delete-test", @@ -269,9 +269,9 @@ "filePaths": [ "member-access.js" ], - "sha1": "191e1b5188f0e9f15bd1ba61e6e608cc27bcf423", + "sha1": "90c11d04be5443162bc497267825252d029a3343", "gitDir": "test/corpus/repos/javascript", - "sha2": "fc8396189b7d6d34ae7045ef2b8dc0427df6262d" + "sha2": "ad078885ab44c7ee3d783f62cdc366251ccf8968" } ,{ "testCaseDescription": "javascript-member-access-delete-rest-test", @@ -302,7 +302,7 @@ "filePaths": [ "member-access.js" ], - "sha1": "fc8396189b7d6d34ae7045ef2b8dc0427df6262d", + "sha1": "ad078885ab44c7ee3d783f62cdc366251ccf8968", "gitDir": "test/corpus/repos/javascript", - "sha2": "6d6d0fda6116e0504607e3b9d770f51596723212" + "sha2": "34a84c5fb21b25b173aca33ee72df362b955f3ee" }] diff --git a/test/corpus/diff-summaries/javascript/method-call.json b/test/corpus/diff-summaries/javascript/method-call.json index ac2194021..957afb5b1 100644 --- a/test/corpus/diff-summaries/javascript/method-call.json +++ b/test/corpus/diff-summaries/javascript/method-call.json @@ -27,9 +27,9 @@ "filePaths": [ "method-call.js" ], - "sha1": "24037753ea53b15094b5e71eef37b694a5f001fe", + "sha1": "1eac526dd11d55220946d9b6306e3031c11e73a7", "gitDir": "test/corpus/repos/javascript", - "sha2": "ce88a11c4e5b2fac1008456760bec7db01ce7d90" + "sha2": "c5816345fd1905a2f4298ed7529b45295c98cf1e" } ,{ "testCaseDescription": "javascript-method-call-replacement-insert-test", @@ -77,9 +77,9 @@ "filePaths": [ "method-call.js" ], - "sha1": "ce88a11c4e5b2fac1008456760bec7db01ce7d90", + "sha1": "c5816345fd1905a2f4298ed7529b45295c98cf1e", "gitDir": "test/corpus/repos/javascript", - "sha2": "b0a9c2ae55eabfec8e38071ba5e67777bdb6b711" + "sha2": "42bb4713d671009105b1d9ccb7edae5cbf7b2c48" } ,{ "testCaseDescription": "javascript-method-call-delete-insert-test", @@ -123,9 +123,9 @@ "filePaths": [ "method-call.js" ], - "sha1": "b0a9c2ae55eabfec8e38071ba5e67777bdb6b711", + "sha1": "42bb4713d671009105b1d9ccb7edae5cbf7b2c48", "gitDir": "test/corpus/repos/javascript", - "sha2": "2e3e47822227fad89d4c04fcab8864e78275580a" + "sha2": "ed18e03d391621e8d70a67e772d341e26f6465b1" } ,{ "testCaseDescription": "javascript-method-call-replacement-test", @@ -169,9 +169,9 @@ "filePaths": [ "method-call.js" ], - "sha1": "2e3e47822227fad89d4c04fcab8864e78275580a", + "sha1": "ed18e03d391621e8d70a67e772d341e26f6465b1", "gitDir": "test/corpus/repos/javascript", - "sha2": "e4743cb765f3cf98961aee3379aa6e44df5d0044" + "sha2": "0a142682630c961d9ff02801c05cc441e1dd722e" } ,{ "testCaseDescription": "javascript-method-call-delete-replacement-test", @@ -236,9 +236,9 @@ "filePaths": [ "method-call.js" ], - "sha1": "e4743cb765f3cf98961aee3379aa6e44df5d0044", + "sha1": "0a142682630c961d9ff02801c05cc441e1dd722e", "gitDir": "test/corpus/repos/javascript", - "sha2": "7adc939f69779c818eab16bdf36f7825068ed6a9" + "sha2": "95f9b4362d197b6e47e43cf7763c9fe06aff67f2" } ,{ "testCaseDescription": "javascript-method-call-delete-test", @@ -269,9 +269,9 @@ "filePaths": [ "method-call.js" ], - "sha1": "7adc939f69779c818eab16bdf36f7825068ed6a9", + "sha1": "95f9b4362d197b6e47e43cf7763c9fe06aff67f2", "gitDir": "test/corpus/repos/javascript", - "sha2": "9c530a1b7197ec7453b5a4af0600a715768a5727" + "sha2": "fbd02de257a4ec83bb80fc192b629c5fd22a7ea4" } ,{ "testCaseDescription": "javascript-method-call-delete-rest-test", @@ -302,7 +302,7 @@ "filePaths": [ "method-call.js" ], - "sha1": "9c530a1b7197ec7453b5a4af0600a715768a5727", + "sha1": "fbd02de257a4ec83bb80fc192b629c5fd22a7ea4", "gitDir": "test/corpus/repos/javascript", - "sha2": "c64bd8c8fddd5dfddd8b66e5da73f44196a2f949" + "sha2": "90687f3994b4645e5db5b97ec4da3502fbe9053d" }] diff --git a/test/corpus/diff-summaries/javascript/named-function.json b/test/corpus/diff-summaries/javascript/named-function.json index 98f3abc92..2b13f9dfb 100644 --- a/test/corpus/diff-summaries/javascript/named-function.json +++ b/test/corpus/diff-summaries/javascript/named-function.json @@ -27,9 +27,9 @@ "filePaths": [ "named-function.js" ], - "sha1": "13ebce1d1e86a542435c13c42f189fc5f63ffa80", + "sha1": "2757c3a3cfdea7d078af6cd6c05b4355fff8b112", "gitDir": "test/corpus/repos/javascript", - "sha2": "ccf7572d97487c3437622c80426357ea3cdd949c" + "sha2": "661e1891e62dd3ea75b4ba1f716cf5ac3244b54a" } ,{ "testCaseDescription": "javascript-named-function-replacement-insert-test", @@ -77,9 +77,9 @@ "filePaths": [ "named-function.js" ], - "sha1": "ccf7572d97487c3437622c80426357ea3cdd949c", + "sha1": "661e1891e62dd3ea75b4ba1f716cf5ac3244b54a", "gitDir": "test/corpus/repos/javascript", - "sha2": "9aef777bcfa7124d354878123376adb64d0f9b86" + "sha2": "10d7a7acaf524aaf2538b4cf464b62ad3bb8cb73" } ,{ "testCaseDescription": "javascript-named-function-delete-insert-test", @@ -191,9 +191,9 @@ "filePaths": [ "named-function.js" ], - "sha1": "9aef777bcfa7124d354878123376adb64d0f9b86", + "sha1": "10d7a7acaf524aaf2538b4cf464b62ad3bb8cb73", "gitDir": "test/corpus/repos/javascript", - "sha2": "51586f5431494e95c89dbf547d91b89affe41d80" + "sha2": "4fe44583a5a229765f67c4550e2e2a44fe5b910d" } ,{ "testCaseDescription": "javascript-named-function-replacement-test", @@ -305,9 +305,9 @@ "filePaths": [ "named-function.js" ], - "sha1": "51586f5431494e95c89dbf547d91b89affe41d80", + "sha1": "4fe44583a5a229765f67c4550e2e2a44fe5b910d", "gitDir": "test/corpus/repos/javascript", - "sha2": "412499fc3980298e4426f219fc4c7728f7970a2d" + "sha2": "cfb65cb4c10bef064b3811d6d74daa567401b303" } ,{ "testCaseDescription": "javascript-named-function-delete-replacement-test", @@ -372,9 +372,9 @@ "filePaths": [ "named-function.js" ], - "sha1": "412499fc3980298e4426f219fc4c7728f7970a2d", + "sha1": "cfb65cb4c10bef064b3811d6d74daa567401b303", "gitDir": "test/corpus/repos/javascript", - "sha2": "808aa67a46dd08a54a9688644ad1ed7f0a787449" + "sha2": "1fee1c5ce1f374dd5f6fc565a5a95e51c849368f" } ,{ "testCaseDescription": "javascript-named-function-delete-test", @@ -405,9 +405,9 @@ "filePaths": [ "named-function.js" ], - "sha1": "808aa67a46dd08a54a9688644ad1ed7f0a787449", + "sha1": "1fee1c5ce1f374dd5f6fc565a5a95e51c849368f", "gitDir": "test/corpus/repos/javascript", - "sha2": "bc6a204b96bb860353491146bcf0c4adebe28f69" + "sha2": "f4a8c0642e5045127f2f450d9762276ffcb136b2" } ,{ "testCaseDescription": "javascript-named-function-delete-rest-test", @@ -438,7 +438,7 @@ "filePaths": [ "named-function.js" ], - "sha1": "bc6a204b96bb860353491146bcf0c4adebe28f69", + "sha1": "f4a8c0642e5045127f2f450d9762276ffcb136b2", "gitDir": "test/corpus/repos/javascript", - "sha2": "2f07429c5135205d55550f4c64061a6ac987da17" + "sha2": "035ebadb21075a55367b83c380264365799ac421" }] diff --git a/test/corpus/diff-summaries/javascript/nested-functions.json b/test/corpus/diff-summaries/javascript/nested-functions.json index 4a0a83e99..9c62b516f 100644 --- a/test/corpus/diff-summaries/javascript/nested-functions.json +++ b/test/corpus/diff-summaries/javascript/nested-functions.json @@ -27,9 +27,9 @@ "filePaths": [ "nested-functions.js" ], - "sha1": "0ae77f84b193044495c0abfc49d346bde5e39414", + "sha1": "ff9c3e1416340f9c41efe59880ae44b658ff4bf3", "gitDir": "test/corpus/repos/javascript", - "sha2": "ef19570b8866d3b5832b07c94b679e61d4ed5a3d" + "sha2": "fda28c0db6815d7395f08564645db20bef73cc87" } ,{ "testCaseDescription": "javascript-nested-functions-replacement-insert-test", @@ -77,9 +77,9 @@ "filePaths": [ "nested-functions.js" ], - "sha1": "ef19570b8866d3b5832b07c94b679e61d4ed5a3d", + "sha1": "fda28c0db6815d7395f08564645db20bef73cc87", "gitDir": "test/corpus/repos/javascript", - "sha2": "bc194874e5e15edb201005aca9d7b8d4f711053f" + "sha2": "e0170503b1eef4379585fcadaab5c1ce210fac28" } ,{ "testCaseDescription": "javascript-nested-functions-delete-insert-test", @@ -153,9 +153,9 @@ "filePaths": [ "nested-functions.js" ], - "sha1": "bc194874e5e15edb201005aca9d7b8d4f711053f", + "sha1": "e0170503b1eef4379585fcadaab5c1ce210fac28", "gitDir": "test/corpus/repos/javascript", - "sha2": "438e79efdd7784fa092f9832cc689141253b5295" + "sha2": "62a15249f8533d75e77e361ae05bd39673511d2d" } ,{ "testCaseDescription": "javascript-nested-functions-replacement-test", @@ -229,9 +229,9 @@ "filePaths": [ "nested-functions.js" ], - "sha1": "438e79efdd7784fa092f9832cc689141253b5295", + "sha1": "62a15249f8533d75e77e361ae05bd39673511d2d", "gitDir": "test/corpus/repos/javascript", - "sha2": "32af107bcaea5a5ac4849198f2d6227b6015c709" + "sha2": "04f144c9e7008a1fe76b333c0622cada2893f709" } ,{ "testCaseDescription": "javascript-nested-functions-delete-replacement-test", @@ -296,9 +296,9 @@ "filePaths": [ "nested-functions.js" ], - "sha1": "32af107bcaea5a5ac4849198f2d6227b6015c709", + "sha1": "04f144c9e7008a1fe76b333c0622cada2893f709", "gitDir": "test/corpus/repos/javascript", - "sha2": "b547ad567b2c5018f3f02b8dcacd63e2ae8cddc5" + "sha2": "0483a9c0ff8b154901197bcab0131839cf906edc" } ,{ "testCaseDescription": "javascript-nested-functions-delete-test", @@ -329,9 +329,9 @@ "filePaths": [ "nested-functions.js" ], - "sha1": "b547ad567b2c5018f3f02b8dcacd63e2ae8cddc5", + "sha1": "0483a9c0ff8b154901197bcab0131839cf906edc", "gitDir": "test/corpus/repos/javascript", - "sha2": "38b78fc259d249ae1a83a38b5a610b1ea4ffd17b" + "sha2": "a15f05c7885e2efa3515f753ffe6109f2c7430cd" } ,{ "testCaseDescription": "javascript-nested-functions-delete-rest-test", @@ -362,7 +362,7 @@ "filePaths": [ "nested-functions.js" ], - "sha1": "38b78fc259d249ae1a83a38b5a610b1ea4ffd17b", + "sha1": "a15f05c7885e2efa3515f753ffe6109f2c7430cd", "gitDir": "test/corpus/repos/javascript", - "sha2": "f330b79e26d2268d24e9ee9ba1fbb1c94d816e65" + "sha2": "215d10e67e03c8e29f188758043ace6b619b01e5" }] diff --git a/test/corpus/diff-summaries/javascript/null.json b/test/corpus/diff-summaries/javascript/null.json index 998ee744e..2c840d20a 100644 --- a/test/corpus/diff-summaries/javascript/null.json +++ b/test/corpus/diff-summaries/javascript/null.json @@ -27,9 +27,9 @@ "filePaths": [ "null.js" ], - "sha1": "704c62da36013859dd8e6a1139c4d908e22bc980", + "sha1": "71b405a91807f07e6c1c55a71a93c78d07b0b4ab", "gitDir": "test/corpus/repos/javascript", - "sha2": "fb650c97f935c1a723fbfbaa541690a1a5d19c07" + "sha2": "40b103a73134c60adc6ee3ae4902918373b060cf" } ,{ "testCaseDescription": "javascript-null-replacement-insert-test", @@ -77,9 +77,9 @@ "filePaths": [ "null.js" ], - "sha1": "fb650c97f935c1a723fbfbaa541690a1a5d19c07", + "sha1": "40b103a73134c60adc6ee3ae4902918373b060cf", "gitDir": "test/corpus/repos/javascript", - "sha2": "2888848f2fc7ae75b57830fa7d44db6fb618e86f" + "sha2": "39f88f076256d48c52a7b49d2e2a4dbb33b65e1a" } ,{ "testCaseDescription": "javascript-null-delete-insert-test", @@ -127,9 +127,9 @@ "filePaths": [ "null.js" ], - "sha1": "2888848f2fc7ae75b57830fa7d44db6fb618e86f", + "sha1": "39f88f076256d48c52a7b49d2e2a4dbb33b65e1a", "gitDir": "test/corpus/repos/javascript", - "sha2": "67b14c1f2c338f118cc8645a884945ad5b20be5c" + "sha2": "a0b7643968ebb1985deac3297be5a63e84c87ec5" } ,{ "testCaseDescription": "javascript-null-replacement-test", @@ -177,9 +177,9 @@ "filePaths": [ "null.js" ], - "sha1": "67b14c1f2c338f118cc8645a884945ad5b20be5c", + "sha1": "a0b7643968ebb1985deac3297be5a63e84c87ec5", "gitDir": "test/corpus/repos/javascript", - "sha2": "64a2fca3b0468d6445f67bc686e0155eb15a0e6e" + "sha2": "b398a1a9095f31c9f49eb70f76ab7775e0e0b912" } ,{ "testCaseDescription": "javascript-null-delete-replacement-test", @@ -244,9 +244,9 @@ "filePaths": [ "null.js" ], - "sha1": "64a2fca3b0468d6445f67bc686e0155eb15a0e6e", + "sha1": "b398a1a9095f31c9f49eb70f76ab7775e0e0b912", "gitDir": "test/corpus/repos/javascript", - "sha2": "ee2fcf5e976c4a8358149eb56112eaef153c13b2" + "sha2": "9eef1322e7b1b0997a712803355e071fd0cb12da" } ,{ "testCaseDescription": "javascript-null-delete-test", @@ -277,9 +277,9 @@ "filePaths": [ "null.js" ], - "sha1": "ee2fcf5e976c4a8358149eb56112eaef153c13b2", + "sha1": "9eef1322e7b1b0997a712803355e071fd0cb12da", "gitDir": "test/corpus/repos/javascript", - "sha2": "2866dfd579a77d59617dc565a8bc2b0f412b1a5e" + "sha2": "48fea5e1448dcc23d6a626649dec8cdedc67a029" } ,{ "testCaseDescription": "javascript-null-delete-rest-test", @@ -310,7 +310,7 @@ "filePaths": [ "null.js" ], - "sha1": "2866dfd579a77d59617dc565a8bc2b0f412b1a5e", + "sha1": "48fea5e1448dcc23d6a626649dec8cdedc67a029", "gitDir": "test/corpus/repos/javascript", - "sha2": "660e3a5b95669c843b77a62446f2e57dcde9e285" + "sha2": "b12ee7f9618c46965c38b2ba972b8dc99f4db063" }] diff --git a/test/corpus/diff-summaries/javascript/number.json b/test/corpus/diff-summaries/javascript/number.json index 56c91a562..9b36290bb 100644 --- a/test/corpus/diff-summaries/javascript/number.json +++ b/test/corpus/diff-summaries/javascript/number.json @@ -27,9 +27,9 @@ "filePaths": [ "number.js" ], - "sha1": "ede522a00f4676035db2e9d76a9b702e5234917a", + "sha1": "c0f927bdea55b3ee78ee68522ae964808f19fab6", "gitDir": "test/corpus/repos/javascript", - "sha2": "38114803fec2d221d3d6e204766200b7b04e0e27" + "sha2": "14a7034f5e599408ea3a07f7c55fc2713442de61" } ,{ "testCaseDescription": "javascript-number-replacement-insert-test", @@ -77,9 +77,9 @@ "filePaths": [ "number.js" ], - "sha1": "38114803fec2d221d3d6e204766200b7b04e0e27", + "sha1": "14a7034f5e599408ea3a07f7c55fc2713442de61", "gitDir": "test/corpus/repos/javascript", - "sha2": "1545918b32f8c704efe91e7655442e328f98f43d" + "sha2": "cdcfd757586d10a50ea65fad6be0095c3ff0e599" } ,{ "testCaseDescription": "javascript-number-delete-insert-test", @@ -123,9 +123,9 @@ "filePaths": [ "number.js" ], - "sha1": "1545918b32f8c704efe91e7655442e328f98f43d", + "sha1": "cdcfd757586d10a50ea65fad6be0095c3ff0e599", "gitDir": "test/corpus/repos/javascript", - "sha2": "c9fbddc95fbbb9a1acb697c5c072b8ffbe163336" + "sha2": "92ac8953b06044880a975cf28d3c45aab8f88759" } ,{ "testCaseDescription": "javascript-number-replacement-test", @@ -169,9 +169,9 @@ "filePaths": [ "number.js" ], - "sha1": "c9fbddc95fbbb9a1acb697c5c072b8ffbe163336", + "sha1": "92ac8953b06044880a975cf28d3c45aab8f88759", "gitDir": "test/corpus/repos/javascript", - "sha2": "e27818b8f53204e17eb88985eaf49c9ea8ef4726" + "sha2": "dffbcecbd65965443b71665de242c237f4d94513" } ,{ "testCaseDescription": "javascript-number-delete-replacement-test", @@ -236,9 +236,9 @@ "filePaths": [ "number.js" ], - "sha1": "e27818b8f53204e17eb88985eaf49c9ea8ef4726", + "sha1": "dffbcecbd65965443b71665de242c237f4d94513", "gitDir": "test/corpus/repos/javascript", - "sha2": "246413aa97cfb3cfec1874000969cd4374373f15" + "sha2": "fab30a6c3846d6d9ae795337b13541ab3591bf7d" } ,{ "testCaseDescription": "javascript-number-delete-test", @@ -269,9 +269,9 @@ "filePaths": [ "number.js" ], - "sha1": "246413aa97cfb3cfec1874000969cd4374373f15", + "sha1": "fab30a6c3846d6d9ae795337b13541ab3591bf7d", "gitDir": "test/corpus/repos/javascript", - "sha2": "f0b25a1412833d0cdec38e7b8306ab6310704e72" + "sha2": "e3a519863f7404783c22937eac4ab659a4f30f0d" } ,{ "testCaseDescription": "javascript-number-delete-rest-test", @@ -302,7 +302,7 @@ "filePaths": [ "number.js" ], - "sha1": "f0b25a1412833d0cdec38e7b8306ab6310704e72", + "sha1": "e3a519863f7404783c22937eac4ab659a4f30f0d", "gitDir": "test/corpus/repos/javascript", - "sha2": "6539b8361c59312164d8321ca3888c0511fcf849" + "sha2": "76561264ab91701d52dcc8dcbb42c25ea412ae25" }] diff --git a/test/corpus/diff-summaries/javascript/object-with-methods.json b/test/corpus/diff-summaries/javascript/object-with-methods.json index 850e51b50..0db29037c 100644 --- a/test/corpus/diff-summaries/javascript/object-with-methods.json +++ b/test/corpus/diff-summaries/javascript/object-with-methods.json @@ -27,9 +27,9 @@ "filePaths": [ "objects-with-methods.js" ], - "sha1": "613f8b8ea74085ab35b7398fe3f636eda7d63fa2", + "sha1": "2a302d002490d7bb5aff372747a028cec52c1b4b", "gitDir": "test/corpus/repos/javascript", - "sha2": "2e774e0d6c383c529d88e5606d8696e9ade47af3" + "sha2": "6783a5e813844940dfff6c5636d1461bede9ad38" } ,{ "testCaseDescription": "javascript-objects-with-methods-replacement-insert-test", @@ -77,9 +77,9 @@ "filePaths": [ "objects-with-methods.js" ], - "sha1": "2e774e0d6c383c529d88e5606d8696e9ade47af3", + "sha1": "6783a5e813844940dfff6c5636d1461bede9ad38", "gitDir": "test/corpus/repos/javascript", - "sha2": "9ac75c62eaf7cb66aff208ff41c1c39ea794d7e3" + "sha2": "a213d7d3cf0a804f759d6137db7182fe97a95f1a" } ,{ "testCaseDescription": "javascript-objects-with-methods-delete-insert-test", @@ -123,9 +123,9 @@ "filePaths": [ "objects-with-methods.js" ], - "sha1": "9ac75c62eaf7cb66aff208ff41c1c39ea794d7e3", + "sha1": "a213d7d3cf0a804f759d6137db7182fe97a95f1a", "gitDir": "test/corpus/repos/javascript", - "sha2": "f6d7a1f18d357f526c00dad5ab7e5f4094ff73a0" + "sha2": "b118e4745f2ffd7e7f6d1f9247ec62a7a7a6de21" } ,{ "testCaseDescription": "javascript-objects-with-methods-replacement-test", @@ -169,9 +169,9 @@ "filePaths": [ "objects-with-methods.js" ], - "sha1": "f6d7a1f18d357f526c00dad5ab7e5f4094ff73a0", + "sha1": "b118e4745f2ffd7e7f6d1f9247ec62a7a7a6de21", "gitDir": "test/corpus/repos/javascript", - "sha2": "02512232a51b3f33eace65e85b2ad927a200629d" + "sha2": "856aa7174277d2af3db156663841364743743bf8" } ,{ "testCaseDescription": "javascript-objects-with-methods-delete-replacement-test", @@ -236,9 +236,9 @@ "filePaths": [ "objects-with-methods.js" ], - "sha1": "02512232a51b3f33eace65e85b2ad927a200629d", + "sha1": "856aa7174277d2af3db156663841364743743bf8", "gitDir": "test/corpus/repos/javascript", - "sha2": "52a1106dbdff953a566289445e06998e28f46f03" + "sha2": "9f4f98182b4ee3099d8c8b9437ab3970278a211f" } ,{ "testCaseDescription": "javascript-objects-with-methods-delete-test", @@ -269,9 +269,9 @@ "filePaths": [ "objects-with-methods.js" ], - "sha1": "52a1106dbdff953a566289445e06998e28f46f03", + "sha1": "9f4f98182b4ee3099d8c8b9437ab3970278a211f", "gitDir": "test/corpus/repos/javascript", - "sha2": "6b8bc1f10092271cab628b3e17f13524f28fdded" + "sha2": "fc6f3cd8022124b7746e923db660ebaf4ab20072" } ,{ "testCaseDescription": "javascript-objects-with-methods-delete-rest-test", @@ -302,7 +302,7 @@ "filePaths": [ "objects-with-methods.js" ], - "sha1": "6b8bc1f10092271cab628b3e17f13524f28fdded", + "sha1": "fc6f3cd8022124b7746e923db660ebaf4ab20072", "gitDir": "test/corpus/repos/javascript", - "sha2": "f15ed2c50f158bdc680972378a52575dbc492025" + "sha2": "802ec5ac85b69eebd846079cc2cd500021a32d84" }] diff --git a/test/corpus/diff-summaries/javascript/object.json b/test/corpus/diff-summaries/javascript/object.json index 703279d65..20c277693 100644 --- a/test/corpus/diff-summaries/javascript/object.json +++ b/test/corpus/diff-summaries/javascript/object.json @@ -27,9 +27,9 @@ "filePaths": [ "object.js" ], - "sha1": "f8683054b3df6a44185993d0c11c1edcf4477b16", + "sha1": "f7d88a07b742fd7334d28806f01764ddfed94384", "gitDir": "test/corpus/repos/javascript", - "sha2": "06f986e188881d31280bf61fc28c2427ddeee3d6" + "sha2": "6f8bef4abc5e31e04a543d36be2551dde44e550e" } ,{ "testCaseDescription": "javascript-object-replacement-insert-test", @@ -77,9 +77,9 @@ "filePaths": [ "object.js" ], - "sha1": "06f986e188881d31280bf61fc28c2427ddeee3d6", + "sha1": "6f8bef4abc5e31e04a543d36be2551dde44e550e", "gitDir": "test/corpus/repos/javascript", - "sha2": "452ffb764876adf5738295d2aa3ec48ea9399761" + "sha2": "d7474d4e8300f28a199a968e552de8cae6044b36" } ,{ "testCaseDescription": "javascript-object-delete-insert-test", @@ -127,9 +127,9 @@ "filePaths": [ "object.js" ], - "sha1": "452ffb764876adf5738295d2aa3ec48ea9399761", + "sha1": "d7474d4e8300f28a199a968e552de8cae6044b36", "gitDir": "test/corpus/repos/javascript", - "sha2": "2e57b5ec821611bfbf24b3d9d73e0ea8bee50624" + "sha2": "e10e21b2d9e5e12c61cc17240c59db19ef0d10f7" } ,{ "testCaseDescription": "javascript-object-replacement-test", @@ -177,9 +177,9 @@ "filePaths": [ "object.js" ], - "sha1": "2e57b5ec821611bfbf24b3d9d73e0ea8bee50624", + "sha1": "e10e21b2d9e5e12c61cc17240c59db19ef0d10f7", "gitDir": "test/corpus/repos/javascript", - "sha2": "b7905f5c7b310ff395bb7882055844a18b45baf2" + "sha2": "a7ec58724bdc2f71f12594b83ff1dced76cd1bad" } ,{ "testCaseDescription": "javascript-object-delete-replacement-test", @@ -244,9 +244,9 @@ "filePaths": [ "object.js" ], - "sha1": "b7905f5c7b310ff395bb7882055844a18b45baf2", + "sha1": "a7ec58724bdc2f71f12594b83ff1dced76cd1bad", "gitDir": "test/corpus/repos/javascript", - "sha2": "52c7c26f74741c4f26effb3b6efe111830bb0e0c" + "sha2": "98d31f1f5f2777d2fe89a14ae0d81f6c8b45f98c" } ,{ "testCaseDescription": "javascript-object-delete-test", @@ -277,9 +277,9 @@ "filePaths": [ "object.js" ], - "sha1": "52c7c26f74741c4f26effb3b6efe111830bb0e0c", + "sha1": "98d31f1f5f2777d2fe89a14ae0d81f6c8b45f98c", "gitDir": "test/corpus/repos/javascript", - "sha2": "9ffa4ea63cd2c434126197fb165c67412a4c8130" + "sha2": "8a4a15f9fb5e7993a6e63395aaac3542401d72e2" } ,{ "testCaseDescription": "javascript-object-delete-rest-test", @@ -310,7 +310,7 @@ "filePaths": [ "object.js" ], - "sha1": "9ffa4ea63cd2c434126197fb165c67412a4c8130", + "sha1": "8a4a15f9fb5e7993a6e63395aaac3542401d72e2", "gitDir": "test/corpus/repos/javascript", - "sha2": "b4b200a6398403b141e5fd87506899af661b97a6" + "sha2": "804f2056b155a51e98aacc2af9f2950bab4cbaf8" }] diff --git a/test/corpus/diff-summaries/javascript/regex.json b/test/corpus/diff-summaries/javascript/regex.json index a1e2a55da..776a208e9 100644 --- a/test/corpus/diff-summaries/javascript/regex.json +++ b/test/corpus/diff-summaries/javascript/regex.json @@ -27,9 +27,9 @@ "filePaths": [ "regex.js" ], - "sha1": "1980a80ff9a2f2886b85d2e8ce9df29b1f7adad5", + "sha1": "a2484cda906ab54500ff1a38755f0f7a37c85d77", "gitDir": "test/corpus/repos/javascript", - "sha2": "6a3727ab152c2ce63c9771e6c86f1ce2659a85e2" + "sha2": "ba99759f9b455baaea534db57c0a9bbdf4e784ee" } ,{ "testCaseDescription": "javascript-regex-replacement-insert-test", @@ -77,9 +77,9 @@ "filePaths": [ "regex.js" ], - "sha1": "6a3727ab152c2ce63c9771e6c86f1ce2659a85e2", + "sha1": "ba99759f9b455baaea534db57c0a9bbdf4e784ee", "gitDir": "test/corpus/repos/javascript", - "sha2": "330b5f33c8c67a52d33d007192b6e5e2eca2b6eb" + "sha2": "f89564bc9c495fc245321efc7ce2f893282252f1" } ,{ "testCaseDescription": "javascript-regex-delete-insert-test", @@ -123,9 +123,9 @@ "filePaths": [ "regex.js" ], - "sha1": "330b5f33c8c67a52d33d007192b6e5e2eca2b6eb", + "sha1": "f89564bc9c495fc245321efc7ce2f893282252f1", "gitDir": "test/corpus/repos/javascript", - "sha2": "0df0ff208ecda7e3fe1ec07720ca4e2d5ca97abe" + "sha2": "246cd5b7f230ebefe2653bf0567625dfab2b0b64" } ,{ "testCaseDescription": "javascript-regex-replacement-test", @@ -169,9 +169,9 @@ "filePaths": [ "regex.js" ], - "sha1": "0df0ff208ecda7e3fe1ec07720ca4e2d5ca97abe", + "sha1": "246cd5b7f230ebefe2653bf0567625dfab2b0b64", "gitDir": "test/corpus/repos/javascript", - "sha2": "815037f8db1286618f7fe00d93247c8abeec2e8b" + "sha2": "20f06465056f68cd4dbd3da5f65b5e1e61a5f2a3" } ,{ "testCaseDescription": "javascript-regex-delete-replacement-test", @@ -236,9 +236,9 @@ "filePaths": [ "regex.js" ], - "sha1": "815037f8db1286618f7fe00d93247c8abeec2e8b", + "sha1": "20f06465056f68cd4dbd3da5f65b5e1e61a5f2a3", "gitDir": "test/corpus/repos/javascript", - "sha2": "085e1d0671ddbeb65df8785014418f4dd5e406fb" + "sha2": "1adb4501e159734dc46acc505ee11e5a633493a7" } ,{ "testCaseDescription": "javascript-regex-delete-test", @@ -269,9 +269,9 @@ "filePaths": [ "regex.js" ], - "sha1": "085e1d0671ddbeb65df8785014418f4dd5e406fb", + "sha1": "1adb4501e159734dc46acc505ee11e5a633493a7", "gitDir": "test/corpus/repos/javascript", - "sha2": "2320ce8ffa14273ff3094b25c293920a117cdfb5" + "sha2": "04bdd6c2c747af7d555e7dc76c31bcb840ffa7e5" } ,{ "testCaseDescription": "javascript-regex-delete-rest-test", @@ -302,7 +302,7 @@ "filePaths": [ "regex.js" ], - "sha1": "2320ce8ffa14273ff3094b25c293920a117cdfb5", + "sha1": "04bdd6c2c747af7d555e7dc76c31bcb840ffa7e5", "gitDir": "test/corpus/repos/javascript", - "sha2": "b8ad05d0253ae191a5f160e7048edd003cbfd266" + "sha2": "88eddedb2d7666ebcc74cb1693e7f24e13e4e481" }] diff --git a/test/corpus/diff-summaries/javascript/relational-operator.json b/test/corpus/diff-summaries/javascript/relational-operator.json index 8d307fe06..27e1eb088 100644 --- a/test/corpus/diff-summaries/javascript/relational-operator.json +++ b/test/corpus/diff-summaries/javascript/relational-operator.json @@ -27,9 +27,9 @@ "filePaths": [ "relational-operator.js" ], - "sha1": "44726d92bc92a8541b8e3089ee22826fa31cdc69", + "sha1": "088c27d2d4e2150bac4bff85c129df8d90a407c2", "gitDir": "test/corpus/repos/javascript", - "sha2": "a33204dd9472bf38dca8550758c5c87b533204e5" + "sha2": "99896fdbbc5545bb0eee52c97120fa5150d94611" } ,{ "testCaseDescription": "javascript-relational-operator-replacement-insert-test", @@ -77,9 +77,9 @@ "filePaths": [ "relational-operator.js" ], - "sha1": "a33204dd9472bf38dca8550758c5c87b533204e5", + "sha1": "99896fdbbc5545bb0eee52c97120fa5150d94611", "gitDir": "test/corpus/repos/javascript", - "sha2": "2b464738a19e0a18863b2a4f8a656e9416dcfffc" + "sha2": "bbd92da747e4f47fad4edaf1195dadc110d799b9" } ,{ "testCaseDescription": "javascript-relational-operator-delete-insert-test", @@ -90,9 +90,9 @@ "filePaths": [ "relational-operator.js" ], - "sha1": "2b464738a19e0a18863b2a4f8a656e9416dcfffc", + "sha1": "bbd92da747e4f47fad4edaf1195dadc110d799b9", "gitDir": "test/corpus/repos/javascript", - "sha2": "48ed1f73ff525a6ec7c6cda70d4f9587102dab7d" + "sha2": "d9d45f12405ddc916f2f65a1b13d36db0fc8985c" } ,{ "testCaseDescription": "javascript-relational-operator-replacement-test", @@ -103,9 +103,9 @@ "filePaths": [ "relational-operator.js" ], - "sha1": "48ed1f73ff525a6ec7c6cda70d4f9587102dab7d", + "sha1": "d9d45f12405ddc916f2f65a1b13d36db0fc8985c", "gitDir": "test/corpus/repos/javascript", - "sha2": "db672c2dad46487be60f96146b29937c001ba2b1" + "sha2": "341f8be98d72057a2d1736e13143bc898c9b8e93" } ,{ "testCaseDescription": "javascript-relational-operator-delete-replacement-test", @@ -136,9 +136,9 @@ "filePaths": [ "relational-operator.js" ], - "sha1": "db672c2dad46487be60f96146b29937c001ba2b1", + "sha1": "341f8be98d72057a2d1736e13143bc898c9b8e93", "gitDir": "test/corpus/repos/javascript", - "sha2": "bd6cf287a138becb71cae777b80c5395be91d0d6" + "sha2": "9e5a228fb034020f7bc62fc7200a359f597cdb08" } ,{ "testCaseDescription": "javascript-relational-operator-delete-test", @@ -169,9 +169,9 @@ "filePaths": [ "relational-operator.js" ], - "sha1": "bd6cf287a138becb71cae777b80c5395be91d0d6", + "sha1": "9e5a228fb034020f7bc62fc7200a359f597cdb08", "gitDir": "test/corpus/repos/javascript", - "sha2": "aa476186f44557e5ab77592974a40ff32534eab7" + "sha2": "8e766c6c2f81c0364155153280eb3508335180ce" } ,{ "testCaseDescription": "javascript-relational-operator-delete-rest-test", @@ -202,7 +202,7 @@ "filePaths": [ "relational-operator.js" ], - "sha1": "aa476186f44557e5ab77592974a40ff32534eab7", + "sha1": "8e766c6c2f81c0364155153280eb3508335180ce", "gitDir": "test/corpus/repos/javascript", - "sha2": "af26873a60eeb28bb292941d2ee8cae7449c9a37" + "sha2": "0f63f399f084244c4cfcd918876a8c5e659e8ade" }] diff --git a/test/corpus/diff-summaries/javascript/return-statement.json b/test/corpus/diff-summaries/javascript/return-statement.json index f4078fb53..4235f50c6 100644 --- a/test/corpus/diff-summaries/javascript/return-statement.json +++ b/test/corpus/diff-summaries/javascript/return-statement.json @@ -27,9 +27,9 @@ "filePaths": [ "return-statement.js" ], - "sha1": "c2a48d97ae6754bf21e1dbfa2e13bde3f68deb9c", + "sha1": "fd292d1b33fb3253b0d0f66bae29de22c247d85c", "gitDir": "test/corpus/repos/javascript", - "sha2": "f16f5a51f1d033e808ef534924e1d91c77775b2e" + "sha2": "39c3556dd3f840127f75e3c79588e7f511f3bcd7" } ,{ "testCaseDescription": "javascript-return-statement-replacement-insert-test", @@ -77,9 +77,9 @@ "filePaths": [ "return-statement.js" ], - "sha1": "f16f5a51f1d033e808ef534924e1d91c77775b2e", + "sha1": "39c3556dd3f840127f75e3c79588e7f511f3bcd7", "gitDir": "test/corpus/repos/javascript", - "sha2": "bdacda3ebb5cc26919466bb73dfdd7bc1f50861e" + "sha2": "06973c03af9ae606230fc06efbe7eeab89189937" } ,{ "testCaseDescription": "javascript-return-statement-delete-insert-test", @@ -110,9 +110,9 @@ "filePaths": [ "return-statement.js" ], - "sha1": "bdacda3ebb5cc26919466bb73dfdd7bc1f50861e", + "sha1": "06973c03af9ae606230fc06efbe7eeab89189937", "gitDir": "test/corpus/repos/javascript", - "sha2": "515deebc3a3b05742d2019379e43d547b4d2f3e7" + "sha2": "59a474f44f6019fa35db3ffeecbcd1b302aaf020" } ,{ "testCaseDescription": "javascript-return-statement-replacement-test", @@ -143,9 +143,9 @@ "filePaths": [ "return-statement.js" ], - "sha1": "515deebc3a3b05742d2019379e43d547b4d2f3e7", + "sha1": "59a474f44f6019fa35db3ffeecbcd1b302aaf020", "gitDir": "test/corpus/repos/javascript", - "sha2": "ea03eba44176d1262daab2a8359dea97487df79c" + "sha2": "cbd58b54a42ef7dbca45cb256da3aa7dd40bbf8f" } ,{ "testCaseDescription": "javascript-return-statement-delete-replacement-test", @@ -210,9 +210,9 @@ "filePaths": [ "return-statement.js" ], - "sha1": "ea03eba44176d1262daab2a8359dea97487df79c", + "sha1": "cbd58b54a42ef7dbca45cb256da3aa7dd40bbf8f", "gitDir": "test/corpus/repos/javascript", - "sha2": "f0d57f8e4dc9624fb4d9916a06b52aa20f597a1f" + "sha2": "dd13d4d79b349314a4b9bd2206ab12dbfbcc76b7" } ,{ "testCaseDescription": "javascript-return-statement-delete-test", @@ -243,9 +243,9 @@ "filePaths": [ "return-statement.js" ], - "sha1": "f0d57f8e4dc9624fb4d9916a06b52aa20f597a1f", + "sha1": "dd13d4d79b349314a4b9bd2206ab12dbfbcc76b7", "gitDir": "test/corpus/repos/javascript", - "sha2": "664d2f39a09675e0e17a3e1f595654fbe608b67d" + "sha2": "79c2cb5f5a18808a2d8a5370443f65e371f589cb" } ,{ "testCaseDescription": "javascript-return-statement-delete-rest-test", @@ -276,7 +276,7 @@ "filePaths": [ "return-statement.js" ], - "sha1": "664d2f39a09675e0e17a3e1f595654fbe608b67d", + "sha1": "79c2cb5f5a18808a2d8a5370443f65e371f589cb", "gitDir": "test/corpus/repos/javascript", - "sha2": "07e2e44f7f0b200f4b3454b91a777075ca8a6bf6" + "sha2": "c97ecbdf25494ecedeff774f0dc2dc3e46859eb2" }] diff --git a/test/corpus/diff-summaries/javascript/string.json b/test/corpus/diff-summaries/javascript/string.json index 7174e0e14..9584a362d 100644 --- a/test/corpus/diff-summaries/javascript/string.json +++ b/test/corpus/diff-summaries/javascript/string.json @@ -27,9 +27,9 @@ "filePaths": [ "string.js" ], - "sha1": "f15ed2c50f158bdc680972378a52575dbc492025", + "sha1": "802ec5ac85b69eebd846079cc2cd500021a32d84", "gitDir": "test/corpus/repos/javascript", - "sha2": "9b9896d1260c7f4b9fd7388f1f4b403f6a597d93" + "sha2": "548cff33fc83a827c59de7198e8c91370e15a032" } ,{ "testCaseDescription": "javascript-string-replacement-insert-test", @@ -77,9 +77,9 @@ "filePaths": [ "string.js" ], - "sha1": "9b9896d1260c7f4b9fd7388f1f4b403f6a597d93", + "sha1": "548cff33fc83a827c59de7198e8c91370e15a032", "gitDir": "test/corpus/repos/javascript", - "sha2": "cbcb811994dcd0272b76076688ef0a610d9a4ca5" + "sha2": "1374b4e8911a8aadedf8dd5e08ed34abeb631062" } ,{ "testCaseDescription": "javascript-string-delete-insert-test", @@ -123,9 +123,9 @@ "filePaths": [ "string.js" ], - "sha1": "cbcb811994dcd0272b76076688ef0a610d9a4ca5", + "sha1": "1374b4e8911a8aadedf8dd5e08ed34abeb631062", "gitDir": "test/corpus/repos/javascript", - "sha2": "d86a5265e2bccf5373edf45ce3cf23c44f0cd605" + "sha2": "6d07e2009288c2a768cd297475105b5b41da7090" } ,{ "testCaseDescription": "javascript-string-replacement-test", @@ -169,9 +169,9 @@ "filePaths": [ "string.js" ], - "sha1": "d86a5265e2bccf5373edf45ce3cf23c44f0cd605", + "sha1": "6d07e2009288c2a768cd297475105b5b41da7090", "gitDir": "test/corpus/repos/javascript", - "sha2": "c8b7ef7072fa07bd00b6784fbde52b446fb338e9" + "sha2": "b87c05c3b0d2f211e6f9672c8d7d27b6c7572b58" } ,{ "testCaseDescription": "javascript-string-delete-replacement-test", @@ -236,9 +236,9 @@ "filePaths": [ "string.js" ], - "sha1": "c8b7ef7072fa07bd00b6784fbde52b446fb338e9", + "sha1": "b87c05c3b0d2f211e6f9672c8d7d27b6c7572b58", "gitDir": "test/corpus/repos/javascript", - "sha2": "298da348c90a750fb5171af2a58d8813eb064f8f" + "sha2": "afbfb5f5d581d7a3a75d92c1ce2d8d4271889982" } ,{ "testCaseDescription": "javascript-string-delete-test", @@ -269,9 +269,9 @@ "filePaths": [ "string.js" ], - "sha1": "298da348c90a750fb5171af2a58d8813eb064f8f", + "sha1": "afbfb5f5d581d7a3a75d92c1ce2d8d4271889982", "gitDir": "test/corpus/repos/javascript", - "sha2": "8c867f1717adf94286335d942f2a343c759e2d07" + "sha2": "c78c48f8200e0c64c908a50aa9f96c73e69f27d8" } ,{ "testCaseDescription": "javascript-string-delete-rest-test", @@ -302,7 +302,7 @@ "filePaths": [ "string.js" ], - "sha1": "8c867f1717adf94286335d942f2a343c759e2d07", + "sha1": "c78c48f8200e0c64c908a50aa9f96c73e69f27d8", "gitDir": "test/corpus/repos/javascript", - "sha2": "ede522a00f4676035db2e9d76a9b702e5234917a" + "sha2": "c0f927bdea55b3ee78ee68522ae964808f19fab6" }] diff --git a/test/corpus/diff-summaries/javascript/subscript-access-assignment.json b/test/corpus/diff-summaries/javascript/subscript-access-assignment.json index 36d2f2b76..68d55a251 100644 --- a/test/corpus/diff-summaries/javascript/subscript-access-assignment.json +++ b/test/corpus/diff-summaries/javascript/subscript-access-assignment.json @@ -27,9 +27,9 @@ "filePaths": [ "subscript-access-assignment.js" ], - "sha1": "e7314eba8beae9be9a34bcf91157e5e542f4b2a9", + "sha1": "1e25a73e1015c39932d3a621daa9081a4e46a9ba", "gitDir": "test/corpus/repos/javascript", - "sha2": "2dcf6f61922c7877db63fc6e1160809305c734fc" + "sha2": "feb25a87a8184064cf072dad1c33328049903fa8" } ,{ "testCaseDescription": "javascript-subscript-access-assignment-replacement-insert-test", @@ -77,9 +77,9 @@ "filePaths": [ "subscript-access-assignment.js" ], - "sha1": "2dcf6f61922c7877db63fc6e1160809305c734fc", + "sha1": "feb25a87a8184064cf072dad1c33328049903fa8", "gitDir": "test/corpus/repos/javascript", - "sha2": "da6d1a9623b7a97faec75d5384358f7f8593f799" + "sha2": "da4c6b87c8d120543ffd635714faa321f07480d0" } ,{ "testCaseDescription": "javascript-subscript-access-assignment-delete-insert-test", @@ -123,9 +123,9 @@ "filePaths": [ "subscript-access-assignment.js" ], - "sha1": "da6d1a9623b7a97faec75d5384358f7f8593f799", + "sha1": "da4c6b87c8d120543ffd635714faa321f07480d0", "gitDir": "test/corpus/repos/javascript", - "sha2": "8b811c2aa46341ef0e9edcf76b101e169478425f" + "sha2": "5661d8e351a9843d177881f6aa08f4c88396521f" } ,{ "testCaseDescription": "javascript-subscript-access-assignment-replacement-test", @@ -169,9 +169,9 @@ "filePaths": [ "subscript-access-assignment.js" ], - "sha1": "8b811c2aa46341ef0e9edcf76b101e169478425f", + "sha1": "5661d8e351a9843d177881f6aa08f4c88396521f", "gitDir": "test/corpus/repos/javascript", - "sha2": "cd0920678a4dda65b9457809726f0f1fcd82fe32" + "sha2": "ab82b8ef3a5d6dcaed9da20dd7a3419f22819cba" } ,{ "testCaseDescription": "javascript-subscript-access-assignment-delete-replacement-test", @@ -236,9 +236,9 @@ "filePaths": [ "subscript-access-assignment.js" ], - "sha1": "cd0920678a4dda65b9457809726f0f1fcd82fe32", + "sha1": "ab82b8ef3a5d6dcaed9da20dd7a3419f22819cba", "gitDir": "test/corpus/repos/javascript", - "sha2": "5eec10c41bb97d646fb56a6bc004589909467a6e" + "sha2": "b6efb4049da7e27baf2a0d640a76e8ec471b348a" } ,{ "testCaseDescription": "javascript-subscript-access-assignment-delete-test", @@ -269,9 +269,9 @@ "filePaths": [ "subscript-access-assignment.js" ], - "sha1": "5eec10c41bb97d646fb56a6bc004589909467a6e", + "sha1": "b6efb4049da7e27baf2a0d640a76e8ec471b348a", "gitDir": "test/corpus/repos/javascript", - "sha2": "4b19e000c5b0de14105304c9d033151a30907c57" + "sha2": "457674cd9d6b7c24f7eb6d98253aaa53783975e0" } ,{ "testCaseDescription": "javascript-subscript-access-assignment-delete-rest-test", @@ -302,7 +302,7 @@ "filePaths": [ "subscript-access-assignment.js" ], - "sha1": "4b19e000c5b0de14105304c9d033151a30907c57", + "sha1": "457674cd9d6b7c24f7eb6d98253aaa53783975e0", "gitDir": "test/corpus/repos/javascript", - "sha2": "439dff969c87787fe222d1721433c8fafb0f1a89" + "sha2": "462756b98c54f0b7551f56ee43c309cf51fd64a2" }] diff --git a/test/corpus/diff-summaries/javascript/subscript-access-string.json b/test/corpus/diff-summaries/javascript/subscript-access-string.json index 39d90e355..350e5a462 100644 --- a/test/corpus/diff-summaries/javascript/subscript-access-string.json +++ b/test/corpus/diff-summaries/javascript/subscript-access-string.json @@ -27,9 +27,9 @@ "filePaths": [ "subscript-access-string.js" ], - "sha1": "3df0f065d7b873dd4eba9b0ca3ab7ec5820f3906", + "sha1": "6157ae1cfd3503d356c628a06d397a81757e54f4", "gitDir": "test/corpus/repos/javascript", - "sha2": "108b26851b71b6768ab94313c970479637d5a048" + "sha2": "08e9034b9ef6e3217012295e66c7382e01880c99" } ,{ "testCaseDescription": "javascript-subscript-access-string-replacement-insert-test", @@ -77,9 +77,9 @@ "filePaths": [ "subscript-access-string.js" ], - "sha1": "108b26851b71b6768ab94313c970479637d5a048", + "sha1": "08e9034b9ef6e3217012295e66c7382e01880c99", "gitDir": "test/corpus/repos/javascript", - "sha2": "b4cf95e3d18f381f29116f92faa6c956c93798eb" + "sha2": "81eedf476b04fde83921c08252fc8e7a2919d538" } ,{ "testCaseDescription": "javascript-subscript-access-string-delete-insert-test", @@ -123,9 +123,9 @@ "filePaths": [ "subscript-access-string.js" ], - "sha1": "b4cf95e3d18f381f29116f92faa6c956c93798eb", + "sha1": "81eedf476b04fde83921c08252fc8e7a2919d538", "gitDir": "test/corpus/repos/javascript", - "sha2": "a6ee628c26779ca0148017f0f302db74d74756ca" + "sha2": "5ae81906741dac99bbee475ab6f691d3f8e1d2f5" } ,{ "testCaseDescription": "javascript-subscript-access-string-replacement-test", @@ -169,9 +169,9 @@ "filePaths": [ "subscript-access-string.js" ], - "sha1": "a6ee628c26779ca0148017f0f302db74d74756ca", + "sha1": "5ae81906741dac99bbee475ab6f691d3f8e1d2f5", "gitDir": "test/corpus/repos/javascript", - "sha2": "007983b635c9d206aaf43d9057ae073c5e26fc6d" + "sha2": "782ec6465c6cbcb66f2c76656667cb580783e295" } ,{ "testCaseDescription": "javascript-subscript-access-string-delete-replacement-test", @@ -236,9 +236,9 @@ "filePaths": [ "subscript-access-string.js" ], - "sha1": "007983b635c9d206aaf43d9057ae073c5e26fc6d", + "sha1": "782ec6465c6cbcb66f2c76656667cb580783e295", "gitDir": "test/corpus/repos/javascript", - "sha2": "ab8fffe8032e5c03df3a9f15e4e7c4531efef0ec" + "sha2": "8330dd9edc9588468c3f7d5ecd5361b4b8b069fc" } ,{ "testCaseDescription": "javascript-subscript-access-string-delete-test", @@ -269,9 +269,9 @@ "filePaths": [ "subscript-access-string.js" ], - "sha1": "ab8fffe8032e5c03df3a9f15e4e7c4531efef0ec", + "sha1": "8330dd9edc9588468c3f7d5ecd5361b4b8b069fc", "gitDir": "test/corpus/repos/javascript", - "sha2": "d2ad24f037597d94d511fd2264fd26d453969c27" + "sha2": "2b39a76e2c82616a1bbe59de9ee12700e302a5bb" } ,{ "testCaseDescription": "javascript-subscript-access-string-delete-rest-test", @@ -302,7 +302,7 @@ "filePaths": [ "subscript-access-string.js" ], - "sha1": "d2ad24f037597d94d511fd2264fd26d453969c27", + "sha1": "2b39a76e2c82616a1bbe59de9ee12700e302a5bb", "gitDir": "test/corpus/repos/javascript", - "sha2": "41bf287dfe63a1096787b4f7409a469d078c25b7" + "sha2": "9dc1c8722d84e3f245688e90b8cf7155c95f446f" }] diff --git a/test/corpus/diff-summaries/javascript/subscript-access-variable.json b/test/corpus/diff-summaries/javascript/subscript-access-variable.json index ed1d3f0d2..d03fa8e22 100644 --- a/test/corpus/diff-summaries/javascript/subscript-access-variable.json +++ b/test/corpus/diff-summaries/javascript/subscript-access-variable.json @@ -27,9 +27,9 @@ "filePaths": [ "subscript-access-variable.js" ], - "sha1": "6d6d0fda6116e0504607e3b9d770f51596723212", + "sha1": "34a84c5fb21b25b173aca33ee72df362b955f3ee", "gitDir": "test/corpus/repos/javascript", - "sha2": "e9f0a782313a5481e7aacda482f9a7db8bbb71ab" + "sha2": "ccca96ceb275d35019acee7af10cec4dcb9c140e" } ,{ "testCaseDescription": "javascript-subscript-access-variable-replacement-insert-test", @@ -77,9 +77,9 @@ "filePaths": [ "subscript-access-variable.js" ], - "sha1": "e9f0a782313a5481e7aacda482f9a7db8bbb71ab", + "sha1": "ccca96ceb275d35019acee7af10cec4dcb9c140e", "gitDir": "test/corpus/repos/javascript", - "sha2": "b8ee9f93050067378e2b6da9e2babaecb45915f4" + "sha2": "14446e4157483ffafdd7e5ed66d7093ab0a6076b" } ,{ "testCaseDescription": "javascript-subscript-access-variable-delete-insert-test", @@ -123,9 +123,9 @@ "filePaths": [ "subscript-access-variable.js" ], - "sha1": "b8ee9f93050067378e2b6da9e2babaecb45915f4", + "sha1": "14446e4157483ffafdd7e5ed66d7093ab0a6076b", "gitDir": "test/corpus/repos/javascript", - "sha2": "1b79e00006cb344b231833c29178306caf8374f6" + "sha2": "1d98a4fb0a9300fc55f4533eb6f30e75e4a3be3b" } ,{ "testCaseDescription": "javascript-subscript-access-variable-replacement-test", @@ -169,9 +169,9 @@ "filePaths": [ "subscript-access-variable.js" ], - "sha1": "1b79e00006cb344b231833c29178306caf8374f6", + "sha1": "1d98a4fb0a9300fc55f4533eb6f30e75e4a3be3b", "gitDir": "test/corpus/repos/javascript", - "sha2": "1212ba90e58487b5994b8b685786461fe55bc66b" + "sha2": "4a34ec4c1e6412c882409c83c46b8d2612543cbd" } ,{ "testCaseDescription": "javascript-subscript-access-variable-delete-replacement-test", @@ -236,9 +236,9 @@ "filePaths": [ "subscript-access-variable.js" ], - "sha1": "1212ba90e58487b5994b8b685786461fe55bc66b", + "sha1": "4a34ec4c1e6412c882409c83c46b8d2612543cbd", "gitDir": "test/corpus/repos/javascript", - "sha2": "48061d0539866aebd56ffa52b4210ac55cb87ad9" + "sha2": "cc7e39b323d13e1f410286e56d0fb0128950d715" } ,{ "testCaseDescription": "javascript-subscript-access-variable-delete-test", @@ -269,9 +269,9 @@ "filePaths": [ "subscript-access-variable.js" ], - "sha1": "48061d0539866aebd56ffa52b4210ac55cb87ad9", + "sha1": "cc7e39b323d13e1f410286e56d0fb0128950d715", "gitDir": "test/corpus/repos/javascript", - "sha2": "b271584c1989c4968ad62cdeec000ed54714db57" + "sha2": "f21d7b5aa1767f892bf1d76df7ade14f62d7e749" } ,{ "testCaseDescription": "javascript-subscript-access-variable-delete-rest-test", @@ -302,7 +302,7 @@ "filePaths": [ "subscript-access-variable.js" ], - "sha1": "b271584c1989c4968ad62cdeec000ed54714db57", + "sha1": "f21d7b5aa1767f892bf1d76df7ade14f62d7e749", "gitDir": "test/corpus/repos/javascript", - "sha2": "3df0f065d7b873dd4eba9b0ca3ab7ec5820f3906" + "sha2": "6157ae1cfd3503d356c628a06d397a81757e54f4" }] diff --git a/test/corpus/diff-summaries/javascript/switch-statement.json b/test/corpus/diff-summaries/javascript/switch-statement.json index 0c6781cd7..e19cd0ddf 100644 --- a/test/corpus/diff-summaries/javascript/switch-statement.json +++ b/test/corpus/diff-summaries/javascript/switch-statement.json @@ -27,9 +27,9 @@ "filePaths": [ "switch-statement.js" ], - "sha1": "011a5d6edc417ef0abbfb325ad08abdb917f4184", + "sha1": "7d081d5591b64adba332f89a0a3aeba494aa1b0e", "gitDir": "test/corpus/repos/javascript", - "sha2": "f5f92d14854e8f589966634672d4609022ac912d" + "sha2": "810a8ba269ce2c084bdd064eb49b2f48e0d9a623" } ,{ "testCaseDescription": "javascript-switch-statement-replacement-insert-test", @@ -77,9 +77,9 @@ "filePaths": [ "switch-statement.js" ], - "sha1": "f5f92d14854e8f589966634672d4609022ac912d", + "sha1": "810a8ba269ce2c084bdd064eb49b2f48e0d9a623", "gitDir": "test/corpus/repos/javascript", - "sha2": "430a3d8b360e5f9b8ecccddc9ff00ca703814f57" + "sha2": "ab54c903bdfdd5daba8364e3500bc6c49b39be5c" } ,{ "testCaseDescription": "javascript-switch-statement-delete-insert-test", @@ -153,9 +153,9 @@ "filePaths": [ "switch-statement.js" ], - "sha1": "430a3d8b360e5f9b8ecccddc9ff00ca703814f57", + "sha1": "ab54c903bdfdd5daba8364e3500bc6c49b39be5c", "gitDir": "test/corpus/repos/javascript", - "sha2": "dd86d549c061ad1000cf990d4056446a70c961cd" + "sha2": "5739e34c49d07d0c4f4796d50bc226e410898aa5" } ,{ "testCaseDescription": "javascript-switch-statement-replacement-test", @@ -229,9 +229,9 @@ "filePaths": [ "switch-statement.js" ], - "sha1": "dd86d549c061ad1000cf990d4056446a70c961cd", + "sha1": "5739e34c49d07d0c4f4796d50bc226e410898aa5", "gitDir": "test/corpus/repos/javascript", - "sha2": "cdb0eb167d6389aa9197e522627b06128c5e6e30" + "sha2": "5ede9d3d51ac8a5d2b5b82baca9ee75cdca1dd00" } ,{ "testCaseDescription": "javascript-switch-statement-delete-replacement-test", @@ -296,9 +296,9 @@ "filePaths": [ "switch-statement.js" ], - "sha1": "cdb0eb167d6389aa9197e522627b06128c5e6e30", + "sha1": "5ede9d3d51ac8a5d2b5b82baca9ee75cdca1dd00", "gitDir": "test/corpus/repos/javascript", - "sha2": "086b2cad74172543d1cec8e29c55aad910c91e9e" + "sha2": "d156d794fda50ada98b7825eebd0f3e420785a6b" } ,{ "testCaseDescription": "javascript-switch-statement-delete-test", @@ -329,9 +329,9 @@ "filePaths": [ "switch-statement.js" ], - "sha1": "086b2cad74172543d1cec8e29c55aad910c91e9e", + "sha1": "d156d794fda50ada98b7825eebd0f3e420785a6b", "gitDir": "test/corpus/repos/javascript", - "sha2": "17867521083f4d60703aa5cc5c8ff5895d36222b" + "sha2": "9fa78cd32cd480820b95fbb40ea837dae8d98019" } ,{ "testCaseDescription": "javascript-switch-statement-delete-rest-test", @@ -362,7 +362,7 @@ "filePaths": [ "switch-statement.js" ], - "sha1": "17867521083f4d60703aa5cc5c8ff5895d36222b", + "sha1": "9fa78cd32cd480820b95fbb40ea837dae8d98019", "gitDir": "test/corpus/repos/javascript", - "sha2": "fa5454a8c0278ac9d3451b8e7c780936c149d8a2" + "sha2": "d3cabdc9dab4bc3c11777bbc5a792d76b819c732" }] diff --git a/test/corpus/diff-summaries/javascript/template-string.json b/test/corpus/diff-summaries/javascript/template-string.json index bb9af2675..7816ccad1 100644 --- a/test/corpus/diff-summaries/javascript/template-string.json +++ b/test/corpus/diff-summaries/javascript/template-string.json @@ -27,9 +27,9 @@ "filePaths": [ "template-string.js" ], - "sha1": "b68fd6fad9ad8bbfb5fef0b97e42bb9899f01a0e", + "sha1": "b2046cbd2baf7870677913d1acc35696f7a97f84", "gitDir": "test/corpus/repos/javascript", - "sha2": "90f174d23bcb10dbc060ff7543e69b0cf69a5279" + "sha2": "86eea3a9c43e1c8981341e2d81fdb8b21ef67e38" } ,{ "testCaseDescription": "javascript-template-string-replacement-insert-test", @@ -77,9 +77,9 @@ "filePaths": [ "template-string.js" ], - "sha1": "90f174d23bcb10dbc060ff7543e69b0cf69a5279", + "sha1": "86eea3a9c43e1c8981341e2d81fdb8b21ef67e38", "gitDir": "test/corpus/repos/javascript", - "sha2": "024eb7615d8a0d8a89c72fd12d8a410d8552e78e" + "sha2": "cd8c59b544053f3b2b9e11384660f27ee3060ec8" } ,{ "testCaseDescription": "javascript-template-string-delete-insert-test", @@ -123,9 +123,9 @@ "filePaths": [ "template-string.js" ], - "sha1": "024eb7615d8a0d8a89c72fd12d8a410d8552e78e", + "sha1": "cd8c59b544053f3b2b9e11384660f27ee3060ec8", "gitDir": "test/corpus/repos/javascript", - "sha2": "a579cb4d6d75b2ecd6de1eca964770a557872ad3" + "sha2": "212a15e06fdc26f0dd40b668e1e6c95888476a84" } ,{ "testCaseDescription": "javascript-template-string-replacement-test", @@ -169,9 +169,9 @@ "filePaths": [ "template-string.js" ], - "sha1": "a579cb4d6d75b2ecd6de1eca964770a557872ad3", + "sha1": "212a15e06fdc26f0dd40b668e1e6c95888476a84", "gitDir": "test/corpus/repos/javascript", - "sha2": "0d344fd755f42e0ea79f5f81bc95b0ada2e28c6f" + "sha2": "16a3b8a4889116cd87e1421ca5336dc2512a9f71" } ,{ "testCaseDescription": "javascript-template-string-delete-replacement-test", @@ -236,9 +236,9 @@ "filePaths": [ "template-string.js" ], - "sha1": "0d344fd755f42e0ea79f5f81bc95b0ada2e28c6f", + "sha1": "16a3b8a4889116cd87e1421ca5336dc2512a9f71", "gitDir": "test/corpus/repos/javascript", - "sha2": "96ca5ba0f4d011b95915561b4df40eec68e64d88" + "sha2": "da33d916e0e5bb8f980a2225a65c9518e0a347e8" } ,{ "testCaseDescription": "javascript-template-string-delete-test", @@ -269,9 +269,9 @@ "filePaths": [ "template-string.js" ], - "sha1": "96ca5ba0f4d011b95915561b4df40eec68e64d88", + "sha1": "da33d916e0e5bb8f980a2225a65c9518e0a347e8", "gitDir": "test/corpus/repos/javascript", - "sha2": "e668d0526b3ad687c13bc4ac0e3b606ff8915184" + "sha2": "67b51d8f3b174b011fc32cf8cba64246d727a44d" } ,{ "testCaseDescription": "javascript-template-string-delete-rest-test", @@ -302,7 +302,7 @@ "filePaths": [ "template-string.js" ], - "sha1": "e668d0526b3ad687c13bc4ac0e3b606ff8915184", + "sha1": "67b51d8f3b174b011fc32cf8cba64246d727a44d", "gitDir": "test/corpus/repos/javascript", - "sha2": "17aa0b04103d8aaedf77c3ff72f699f18194a962" + "sha2": "7fe4e0b214260f0482129909a00b5146e3bfc1da" }] diff --git a/test/corpus/diff-summaries/javascript/ternary.json b/test/corpus/diff-summaries/javascript/ternary.json index 1f069ee03..243dc8456 100644 --- a/test/corpus/diff-summaries/javascript/ternary.json +++ b/test/corpus/diff-summaries/javascript/ternary.json @@ -27,9 +27,9 @@ "filePaths": [ "ternary.js" ], - "sha1": "62499db349bd96eba99a785f67d473de8d5b99e6", + "sha1": "e9872de5faf687bc02c8b7a06031ef152b2d3dbe", "gitDir": "test/corpus/repos/javascript", - "sha2": "bc7b9275011e872401a2c3a8c7c17903cdb56169" + "sha2": "d725fe936a6d1727eaaa36abf04dfafcf371ea56" } ,{ "testCaseDescription": "javascript-ternary-replacement-insert-test", @@ -77,9 +77,9 @@ "filePaths": [ "ternary.js" ], - "sha1": "bc7b9275011e872401a2c3a8c7c17903cdb56169", + "sha1": "d725fe936a6d1727eaaa36abf04dfafcf371ea56", "gitDir": "test/corpus/repos/javascript", - "sha2": "b8fea536dd918076cf850567797d069cb7bb324a" + "sha2": "07fff336cbadcbc5323857dccba4368d79c29bfa" } ,{ "testCaseDescription": "javascript-ternary-delete-insert-test", @@ -127,9 +127,9 @@ "filePaths": [ "ternary.js" ], - "sha1": "b8fea536dd918076cf850567797d069cb7bb324a", + "sha1": "07fff336cbadcbc5323857dccba4368d79c29bfa", "gitDir": "test/corpus/repos/javascript", - "sha2": "ed0eb4f64eb99a1de0578efbea21954d506b78ad" + "sha2": "fde4df86574e034afb0c93f8bd4a0d5d0c0f4b93" } ,{ "testCaseDescription": "javascript-ternary-replacement-test", @@ -177,9 +177,9 @@ "filePaths": [ "ternary.js" ], - "sha1": "ed0eb4f64eb99a1de0578efbea21954d506b78ad", + "sha1": "fde4df86574e034afb0c93f8bd4a0d5d0c0f4b93", "gitDir": "test/corpus/repos/javascript", - "sha2": "180368bb326efec93e24d19b6e544eb1c418573b" + "sha2": "4e2cccf815c304ee0fbb9bb5c30aa7ed47545f31" } ,{ "testCaseDescription": "javascript-ternary-delete-replacement-test", @@ -244,9 +244,9 @@ "filePaths": [ "ternary.js" ], - "sha1": "180368bb326efec93e24d19b6e544eb1c418573b", + "sha1": "4e2cccf815c304ee0fbb9bb5c30aa7ed47545f31", "gitDir": "test/corpus/repos/javascript", - "sha2": "c01612a71ed85281bf9c055ad05b6b7ea76377d5" + "sha2": "5902d16d5099cee6b0832454d00c60cf17df43f2" } ,{ "testCaseDescription": "javascript-ternary-delete-test", @@ -277,9 +277,9 @@ "filePaths": [ "ternary.js" ], - "sha1": "c01612a71ed85281bf9c055ad05b6b7ea76377d5", + "sha1": "5902d16d5099cee6b0832454d00c60cf17df43f2", "gitDir": "test/corpus/repos/javascript", - "sha2": "1d83e7224ad50fbbf8712b8cb674512319d379a0" + "sha2": "44fceb27d8f475cff6d431001462c36fa95522f2" } ,{ "testCaseDescription": "javascript-ternary-delete-rest-test", @@ -310,7 +310,7 @@ "filePaths": [ "ternary.js" ], - "sha1": "1d83e7224ad50fbbf8712b8cb674512319d379a0", + "sha1": "44fceb27d8f475cff6d431001462c36fa95522f2", "gitDir": "test/corpus/repos/javascript", - "sha2": "33ac8949dcc8f9f193b6aec3c6d9a5ef26e4bcfd" + "sha2": "3da268bcc8f3c57c756ab27cc04835366de458ed" }] diff --git a/test/corpus/diff-summaries/javascript/this-expression.json b/test/corpus/diff-summaries/javascript/this-expression.json index f0ac71437..cc554d20b 100644 --- a/test/corpus/diff-summaries/javascript/this-expression.json +++ b/test/corpus/diff-summaries/javascript/this-expression.json @@ -27,9 +27,9 @@ "filePaths": [ "this-expression.js" ], - "sha1": "bd9d0d22b6a226d63e44c3d654b6b618571f9912", + "sha1": "562fd7786138fba4253581a1f2995c02007f74b9", "gitDir": "test/corpus/repos/javascript", - "sha2": "9ba0c75c5bc20d8688f51043a458e7d82edf66a7" + "sha2": "8249b4041355beb537fdb71650db090530dec8ef" } ,{ "testCaseDescription": "javascript-this-expression-replacement-insert-test", @@ -77,9 +77,9 @@ "filePaths": [ "this-expression.js" ], - "sha1": "9ba0c75c5bc20d8688f51043a458e7d82edf66a7", + "sha1": "8249b4041355beb537fdb71650db090530dec8ef", "gitDir": "test/corpus/repos/javascript", - "sha2": "6cfe274ee77cd487431fb7a29d6d50cd69ba2582" + "sha2": "33067c8b424eb4ea275b613abdaae3c582423096" } ,{ "testCaseDescription": "javascript-this-expression-delete-insert-test", @@ -127,9 +127,9 @@ "filePaths": [ "this-expression.js" ], - "sha1": "6cfe274ee77cd487431fb7a29d6d50cd69ba2582", + "sha1": "33067c8b424eb4ea275b613abdaae3c582423096", "gitDir": "test/corpus/repos/javascript", - "sha2": "b03e7c6b77cb36d5bfb953572c32ba9b62fb8f3a" + "sha2": "a9b3d6d799f7fae56377bdd4f6a5ccc8d5f8f2bf" } ,{ "testCaseDescription": "javascript-this-expression-replacement-test", @@ -177,9 +177,9 @@ "filePaths": [ "this-expression.js" ], - "sha1": "b03e7c6b77cb36d5bfb953572c32ba9b62fb8f3a", + "sha1": "a9b3d6d799f7fae56377bdd4f6a5ccc8d5f8f2bf", "gitDir": "test/corpus/repos/javascript", - "sha2": "1185333888454aa1868abff45e6110880d636cbe" + "sha2": "246370a44fa4b872413f05c128c04d672eae58fd" } ,{ "testCaseDescription": "javascript-this-expression-delete-replacement-test", @@ -244,9 +244,9 @@ "filePaths": [ "this-expression.js" ], - "sha1": "1185333888454aa1868abff45e6110880d636cbe", + "sha1": "246370a44fa4b872413f05c128c04d672eae58fd", "gitDir": "test/corpus/repos/javascript", - "sha2": "25b9db8ff255f1f8f8a4b47d7f306a274716fe69" + "sha2": "0737c39985667a5e266f35daa5baf2a07a394ad7" } ,{ "testCaseDescription": "javascript-this-expression-delete-test", @@ -277,9 +277,9 @@ "filePaths": [ "this-expression.js" ], - "sha1": "25b9db8ff255f1f8f8a4b47d7f306a274716fe69", + "sha1": "0737c39985667a5e266f35daa5baf2a07a394ad7", "gitDir": "test/corpus/repos/javascript", - "sha2": "381b83d600c8fb17c6fa5ae19c28dd3e02598c84" + "sha2": "4ec6bdcaa9c02dc5d015c368f739cb0fa10f22d9" } ,{ "testCaseDescription": "javascript-this-expression-delete-rest-test", @@ -310,7 +310,7 @@ "filePaths": [ "this-expression.js" ], - "sha1": "381b83d600c8fb17c6fa5ae19c28dd3e02598c84", + "sha1": "4ec6bdcaa9c02dc5d015c368f739cb0fa10f22d9", "gitDir": "test/corpus/repos/javascript", - "sha2": "704c62da36013859dd8e6a1139c4d908e22bc980" + "sha2": "71b405a91807f07e6c1c55a71a93c78d07b0b4ab" }] diff --git a/test/corpus/diff-summaries/javascript/throw-statement.json b/test/corpus/diff-summaries/javascript/throw-statement.json index 6fe00de23..1b3a98d03 100644 --- a/test/corpus/diff-summaries/javascript/throw-statement.json +++ b/test/corpus/diff-summaries/javascript/throw-statement.json @@ -27,9 +27,9 @@ "filePaths": [ "throw-statement.js" ], - "sha1": "fa5454a8c0278ac9d3451b8e7c780936c149d8a2", + "sha1": "d3cabdc9dab4bc3c11777bbc5a792d76b819c732", "gitDir": "test/corpus/repos/javascript", - "sha2": "344d14d1f0e1c27a17ecbc6b83485f3f06c77496" + "sha2": "e81a468723aa03296599372e20ecc7c1251ef654" } ,{ "testCaseDescription": "javascript-throw-statement-replacement-insert-test", @@ -77,9 +77,9 @@ "filePaths": [ "throw-statement.js" ], - "sha1": "344d14d1f0e1c27a17ecbc6b83485f3f06c77496", + "sha1": "e81a468723aa03296599372e20ecc7c1251ef654", "gitDir": "test/corpus/repos/javascript", - "sha2": "34312599d6509f5da3ff900e3b858616aa749b7b" + "sha2": "2a03554ea9e30a920d4fcdbec54c60cba731bb3d" } ,{ "testCaseDescription": "javascript-throw-statement-delete-insert-test", @@ -123,9 +123,9 @@ "filePaths": [ "throw-statement.js" ], - "sha1": "34312599d6509f5da3ff900e3b858616aa749b7b", + "sha1": "2a03554ea9e30a920d4fcdbec54c60cba731bb3d", "gitDir": "test/corpus/repos/javascript", - "sha2": "22a1fffadbd913d4ca3e0eb3d628255ff7b0b380" + "sha2": "206657eed174831f61ce3147f00df2b8ba4c90f3" } ,{ "testCaseDescription": "javascript-throw-statement-replacement-test", @@ -169,9 +169,9 @@ "filePaths": [ "throw-statement.js" ], - "sha1": "22a1fffadbd913d4ca3e0eb3d628255ff7b0b380", + "sha1": "206657eed174831f61ce3147f00df2b8ba4c90f3", "gitDir": "test/corpus/repos/javascript", - "sha2": "a1cd4e7888a7de32aa49e8267348dc595235e201" + "sha2": "1e5ba14bad6d93d8db35db604e0c07b79bf4bb87" } ,{ "testCaseDescription": "javascript-throw-statement-delete-replacement-test", @@ -236,9 +236,9 @@ "filePaths": [ "throw-statement.js" ], - "sha1": "a1cd4e7888a7de32aa49e8267348dc595235e201", + "sha1": "1e5ba14bad6d93d8db35db604e0c07b79bf4bb87", "gitDir": "test/corpus/repos/javascript", - "sha2": "2fb4baa71ca7aeb0ce7b0321b30d926b0a5d3dbf" + "sha2": "c3c3aa05ccd4314717771fa3cfcd116521c4e206" } ,{ "testCaseDescription": "javascript-throw-statement-delete-test", @@ -269,9 +269,9 @@ "filePaths": [ "throw-statement.js" ], - "sha1": "2fb4baa71ca7aeb0ce7b0321b30d926b0a5d3dbf", + "sha1": "c3c3aa05ccd4314717771fa3cfcd116521c4e206", "gitDir": "test/corpus/repos/javascript", - "sha2": "15037656787410bc4177feb4be3ecd795cd600d4" + "sha2": "2a0fa3df9551511efb25e81d813ddb86a843cddf" } ,{ "testCaseDescription": "javascript-throw-statement-delete-rest-test", @@ -302,7 +302,7 @@ "filePaths": [ "throw-statement.js" ], - "sha1": "15037656787410bc4177feb4be3ecd795cd600d4", + "sha1": "2a0fa3df9551511efb25e81d813ddb86a843cddf", "gitDir": "test/corpus/repos/javascript", - "sha2": "fec91a78934dfbf56bb06aa17dfe6d908bf7555f" + "sha2": "37116a9b6cbef2a356805bbeaf6ab65cdcac7749" }] diff --git a/test/corpus/diff-summaries/javascript/true.json b/test/corpus/diff-summaries/javascript/true.json index f47e90b49..420d31512 100644 --- a/test/corpus/diff-summaries/javascript/true.json +++ b/test/corpus/diff-summaries/javascript/true.json @@ -27,9 +27,9 @@ "filePaths": [ "true.js" ], - "sha1": "d75865051390be293044f1901b2de814f883345c", + "sha1": "33c5c1f9cf953a752cbffb621c3f049a1da56ef6", "gitDir": "test/corpus/repos/javascript", - "sha2": "6bfb7dcd9cdede9f50d88268469edcc41bf7a011" + "sha2": "a6ced4af62125992db2e4d0bf35e64a1ac2edec9" } ,{ "testCaseDescription": "javascript-true-replacement-insert-test", @@ -77,9 +77,9 @@ "filePaths": [ "true.js" ], - "sha1": "6bfb7dcd9cdede9f50d88268469edcc41bf7a011", + "sha1": "a6ced4af62125992db2e4d0bf35e64a1ac2edec9", "gitDir": "test/corpus/repos/javascript", - "sha2": "2fb11e227c29c8708462b86607f5898a1526411d" + "sha2": "67c9f34040f63e7c6665a72b86ed606060accbad" } ,{ "testCaseDescription": "javascript-true-delete-insert-test", @@ -127,9 +127,9 @@ "filePaths": [ "true.js" ], - "sha1": "2fb11e227c29c8708462b86607f5898a1526411d", + "sha1": "67c9f34040f63e7c6665a72b86ed606060accbad", "gitDir": "test/corpus/repos/javascript", - "sha2": "44fd30110d94eb034134620ce0043421555609ba" + "sha2": "67f2af6013b86b0ba91f58ea0bb156ab8fef63d9" } ,{ "testCaseDescription": "javascript-true-replacement-test", @@ -177,9 +177,9 @@ "filePaths": [ "true.js" ], - "sha1": "44fd30110d94eb034134620ce0043421555609ba", + "sha1": "67f2af6013b86b0ba91f58ea0bb156ab8fef63d9", "gitDir": "test/corpus/repos/javascript", - "sha2": "865858a52fcb1b2b3425b9edbcfd46170997267f" + "sha2": "20e525bfe23a51c65b7fb2ab38d615b8b79158de" } ,{ "testCaseDescription": "javascript-true-delete-replacement-test", @@ -244,9 +244,9 @@ "filePaths": [ "true.js" ], - "sha1": "865858a52fcb1b2b3425b9edbcfd46170997267f", + "sha1": "20e525bfe23a51c65b7fb2ab38d615b8b79158de", "gitDir": "test/corpus/repos/javascript", - "sha2": "61cd6e15c4e041ff8aa683707a4540122de8560c" + "sha2": "613d3c0edaec792150189c91ad97cc262e325d67" } ,{ "testCaseDescription": "javascript-true-delete-test", @@ -277,9 +277,9 @@ "filePaths": [ "true.js" ], - "sha1": "61cd6e15c4e041ff8aa683707a4540122de8560c", + "sha1": "613d3c0edaec792150189c91ad97cc262e325d67", "gitDir": "test/corpus/repos/javascript", - "sha2": "eddb50d6d415cae98a46191354bc339a1a9634f3" + "sha2": "1d1cf06b41782094ca5aeef9ba6af038f3a58cf8" } ,{ "testCaseDescription": "javascript-true-delete-rest-test", @@ -310,7 +310,7 @@ "filePaths": [ "true.js" ], - "sha1": "eddb50d6d415cae98a46191354bc339a1a9634f3", + "sha1": "1d1cf06b41782094ca5aeef9ba6af038f3a58cf8", "gitDir": "test/corpus/repos/javascript", - "sha2": "0cad1bc8f133de3ec0a2bff083b413422673bbb7" + "sha2": "d72ebc215a9377983c2463fd424f608320626141" }] diff --git a/test/corpus/diff-summaries/javascript/try-statement.json b/test/corpus/diff-summaries/javascript/try-statement.json index 4fba79e1b..82f134c76 100644 --- a/test/corpus/diff-summaries/javascript/try-statement.json +++ b/test/corpus/diff-summaries/javascript/try-statement.json @@ -27,9 +27,9 @@ "filePaths": [ "try-statement.js" ], - "sha1": "fec91a78934dfbf56bb06aa17dfe6d908bf7555f", + "sha1": "37116a9b6cbef2a356805bbeaf6ab65cdcac7749", "gitDir": "test/corpus/repos/javascript", - "sha2": "d4e5fd15a738e341a8e5f579a038aefb05b9ccdf" + "sha2": "a4e8b07dddedfa2d15a61dbb4b3141e2d9f990e2" } ,{ "testCaseDescription": "javascript-try-statement-replacement-insert-test", @@ -77,9 +77,9 @@ "filePaths": [ "try-statement.js" ], - "sha1": "d4e5fd15a738e341a8e5f579a038aefb05b9ccdf", + "sha1": "a4e8b07dddedfa2d15a61dbb4b3141e2d9f990e2", "gitDir": "test/corpus/repos/javascript", - "sha2": "3c0e74e309438cf7cd12e56be343f89f03398ae4" + "sha2": "b7d82c2afa8c802c9cc1f12bf9b1482355e78a72" } ,{ "testCaseDescription": "javascript-try-statement-delete-insert-test", @@ -153,9 +153,9 @@ "filePaths": [ "try-statement.js" ], - "sha1": "3c0e74e309438cf7cd12e56be343f89f03398ae4", + "sha1": "b7d82c2afa8c802c9cc1f12bf9b1482355e78a72", "gitDir": "test/corpus/repos/javascript", - "sha2": "1320684e440745541c94b72e325582231c7baf15" + "sha2": "d226c84d231a5589a524dfefebf69c7f768bdb07" } ,{ "testCaseDescription": "javascript-try-statement-replacement-test", @@ -229,9 +229,9 @@ "filePaths": [ "try-statement.js" ], - "sha1": "1320684e440745541c94b72e325582231c7baf15", + "sha1": "d226c84d231a5589a524dfefebf69c7f768bdb07", "gitDir": "test/corpus/repos/javascript", - "sha2": "770982b7c0e824221296f6aaa73df8284fd754ca" + "sha2": "1f2a4307a65b7dfee0c12be6a32d321219823032" } ,{ "testCaseDescription": "javascript-try-statement-delete-replacement-test", @@ -296,9 +296,9 @@ "filePaths": [ "try-statement.js" ], - "sha1": "770982b7c0e824221296f6aaa73df8284fd754ca", + "sha1": "1f2a4307a65b7dfee0c12be6a32d321219823032", "gitDir": "test/corpus/repos/javascript", - "sha2": "0b1a36ea037d3725f562207d094f1cfb388a90fc" + "sha2": "8c44248e45552ea0890d9af4d83c529c367f0962" } ,{ "testCaseDescription": "javascript-try-statement-delete-test", @@ -329,9 +329,9 @@ "filePaths": [ "try-statement.js" ], - "sha1": "0b1a36ea037d3725f562207d094f1cfb388a90fc", + "sha1": "8c44248e45552ea0890d9af4d83c529c367f0962", "gitDir": "test/corpus/repos/javascript", - "sha2": "0606bc7af03d60fa3b6f7b564b207ff540ccda67" + "sha2": "1cfe73a72235d8cddd34b3b206764bb83c2af7bd" } ,{ "testCaseDescription": "javascript-try-statement-delete-rest-test", @@ -362,7 +362,7 @@ "filePaths": [ "try-statement.js" ], - "sha1": "0606bc7af03d60fa3b6f7b564b207ff540ccda67", + "sha1": "1cfe73a72235d8cddd34b3b206764bb83c2af7bd", "gitDir": "test/corpus/repos/javascript", - "sha2": "1980a80ff9a2f2886b85d2e8ce9df29b1f7adad5" + "sha2": "a2484cda906ab54500ff1a38755f0f7a37c85d77" }] diff --git a/test/corpus/diff-summaries/javascript/type-operator.json b/test/corpus/diff-summaries/javascript/type-operator.json index 73a18c824..dc857dd7b 100644 --- a/test/corpus/diff-summaries/javascript/type-operator.json +++ b/test/corpus/diff-summaries/javascript/type-operator.json @@ -27,9 +27,9 @@ "filePaths": [ "type-operator.js" ], - "sha1": "33ac8949dcc8f9f193b6aec3c6d9a5ef26e4bcfd", + "sha1": "3da268bcc8f3c57c756ab27cc04835366de458ed", "gitDir": "test/corpus/repos/javascript", - "sha2": "c834305365c2c583d268ac9da622e6970389c792" + "sha2": "bf52d2757f0b2aea81872b152a265e458e49a704" } ,{ "testCaseDescription": "javascript-type-operator-replacement-insert-test", @@ -77,9 +77,9 @@ "filePaths": [ "type-operator.js" ], - "sha1": "c834305365c2c583d268ac9da622e6970389c792", + "sha1": "bf52d2757f0b2aea81872b152a265e458e49a704", "gitDir": "test/corpus/repos/javascript", - "sha2": "ec2fb13d8e616b8ec628e5218c4bb18ca8b4cd24" + "sha2": "db902da75db1ceb296f0efcd281f20e06881da2a" } ,{ "testCaseDescription": "javascript-type-operator-delete-insert-test", @@ -110,9 +110,9 @@ "filePaths": [ "type-operator.js" ], - "sha1": "ec2fb13d8e616b8ec628e5218c4bb18ca8b4cd24", + "sha1": "db902da75db1ceb296f0efcd281f20e06881da2a", "gitDir": "test/corpus/repos/javascript", - "sha2": "eb132ce69c3cb4c687bb161634bc0bdb55a8e564" + "sha2": "b1ca63ebe20ccb5ae88740c986028cfe8298f5be" } ,{ "testCaseDescription": "javascript-type-operator-replacement-test", @@ -143,9 +143,9 @@ "filePaths": [ "type-operator.js" ], - "sha1": "eb132ce69c3cb4c687bb161634bc0bdb55a8e564", + "sha1": "b1ca63ebe20ccb5ae88740c986028cfe8298f5be", "gitDir": "test/corpus/repos/javascript", - "sha2": "5c79344eafe1434fb72000c8bfd8bfe22bc990f1" + "sha2": "aa6bcc1ee4c75cdcfa0f9b2a21d70a746a4b841b" } ,{ "testCaseDescription": "javascript-type-operator-delete-replacement-test", @@ -210,9 +210,9 @@ "filePaths": [ "type-operator.js" ], - "sha1": "5c79344eafe1434fb72000c8bfd8bfe22bc990f1", + "sha1": "aa6bcc1ee4c75cdcfa0f9b2a21d70a746a4b841b", "gitDir": "test/corpus/repos/javascript", - "sha2": "1ae514fd9d6e3188404301b117cd0e0bbefd5ed3" + "sha2": "ae4d8cd401ffeba3bc97c02c1524b37cbfb9faea" } ,{ "testCaseDescription": "javascript-type-operator-delete-test", @@ -243,9 +243,9 @@ "filePaths": [ "type-operator.js" ], - "sha1": "1ae514fd9d6e3188404301b117cd0e0bbefd5ed3", + "sha1": "ae4d8cd401ffeba3bc97c02c1524b37cbfb9faea", "gitDir": "test/corpus/repos/javascript", - "sha2": "5d4e55e8afed2e391c912eb255564ec581205e42" + "sha2": "3834bbd6381bbddaac82b11cdcd3081dd861055b" } ,{ "testCaseDescription": "javascript-type-operator-delete-rest-test", @@ -276,7 +276,7 @@ "filePaths": [ "type-operator.js" ], - "sha1": "5d4e55e8afed2e391c912eb255564ec581205e42", + "sha1": "3834bbd6381bbddaac82b11cdcd3081dd861055b", "gitDir": "test/corpus/repos/javascript", - "sha2": "ba1f4c979646df1521e9a187cc24c8b8afc3cd24" + "sha2": "1d2c6fd4f13c50341f68aa3be753d5748c072f12" }] diff --git a/test/corpus/diff-summaries/javascript/undefined.json b/test/corpus/diff-summaries/javascript/undefined.json index b290056b7..bb2cc96c8 100644 --- a/test/corpus/diff-summaries/javascript/undefined.json +++ b/test/corpus/diff-summaries/javascript/undefined.json @@ -27,9 +27,9 @@ "filePaths": [ "undefined.js" ], - "sha1": "660e3a5b95669c843b77a62446f2e57dcde9e285", + "sha1": "b12ee7f9618c46965c38b2ba972b8dc99f4db063", "gitDir": "test/corpus/repos/javascript", - "sha2": "c2db3416e7367c32a0fe0ec5ba7f39f1392205f5" + "sha2": "bb8c48bf8d915b88704830933760b511442cccb9" } ,{ "testCaseDescription": "javascript-undefined-replacement-insert-test", @@ -77,9 +77,9 @@ "filePaths": [ "undefined.js" ], - "sha1": "c2db3416e7367c32a0fe0ec5ba7f39f1392205f5", + "sha1": "bb8c48bf8d915b88704830933760b511442cccb9", "gitDir": "test/corpus/repos/javascript", - "sha2": "849f2668e8c0eb5cad7c9f2013b8260b9b307a70" + "sha2": "300cad620fbf5558e6b7986716bcebe64fd6ebab" } ,{ "testCaseDescription": "javascript-undefined-delete-insert-test", @@ -127,9 +127,9 @@ "filePaths": [ "undefined.js" ], - "sha1": "849f2668e8c0eb5cad7c9f2013b8260b9b307a70", + "sha1": "300cad620fbf5558e6b7986716bcebe64fd6ebab", "gitDir": "test/corpus/repos/javascript", - "sha2": "0a811ae8a68a68c4a1641626085a5190d0a67291" + "sha2": "1dce7dbeb8e1cc5831b8129632f92712b61456ee" } ,{ "testCaseDescription": "javascript-undefined-replacement-test", @@ -177,9 +177,9 @@ "filePaths": [ "undefined.js" ], - "sha1": "0a811ae8a68a68c4a1641626085a5190d0a67291", + "sha1": "1dce7dbeb8e1cc5831b8129632f92712b61456ee", "gitDir": "test/corpus/repos/javascript", - "sha2": "aff5794717cafa1f3c88d9f5062f6df035f1e376" + "sha2": "ccb167578532dd5e532386c33a1d522b8fd740c8" } ,{ "testCaseDescription": "javascript-undefined-delete-replacement-test", @@ -244,9 +244,9 @@ "filePaths": [ "undefined.js" ], - "sha1": "aff5794717cafa1f3c88d9f5062f6df035f1e376", + "sha1": "ccb167578532dd5e532386c33a1d522b8fd740c8", "gitDir": "test/corpus/repos/javascript", - "sha2": "338f22f3617197c3dd81916ddf03e890901a413e" + "sha2": "f9717cc0a960d6c1eb489504d00a3db7b7d4b32f" } ,{ "testCaseDescription": "javascript-undefined-delete-test", @@ -277,9 +277,9 @@ "filePaths": [ "undefined.js" ], - "sha1": "338f22f3617197c3dd81916ddf03e890901a413e", + "sha1": "f9717cc0a960d6c1eb489504d00a3db7b7d4b32f", "gitDir": "test/corpus/repos/javascript", - "sha2": "91fe56f6791949afc929cddd8654bd51b38746cf" + "sha2": "77a27a5f00ff8905174b049ebdb6e592b86277a4" } ,{ "testCaseDescription": "javascript-undefined-delete-rest-test", @@ -310,7 +310,7 @@ "filePaths": [ "undefined.js" ], - "sha1": "91fe56f6791949afc929cddd8654bd51b38746cf", + "sha1": "77a27a5f00ff8905174b049ebdb6e592b86277a4", "gitDir": "test/corpus/repos/javascript", - "sha2": "d75865051390be293044f1901b2de814f883345c" + "sha2": "33c5c1f9cf953a752cbffb621c3f049a1da56ef6" }] diff --git a/test/corpus/diff-summaries/javascript/var-declaration.json b/test/corpus/diff-summaries/javascript/var-declaration.json index 37f08111e..1d5ab9caa 100644 --- a/test/corpus/diff-summaries/javascript/var-declaration.json +++ b/test/corpus/diff-summaries/javascript/var-declaration.json @@ -27,9 +27,9 @@ "filePaths": [ "var-declaration.js" ], - "sha1": "07e2e44f7f0b200f4b3454b91a777075ca8a6bf6", + "sha1": "c97ecbdf25494ecedeff774f0dc2dc3e46859eb2", "gitDir": "test/corpus/repos/javascript", - "sha2": "64fc6fb51d210079cd9afabc5f566604f46e35ba" + "sha2": "eedc2942855b62115ad5dc3a6627b9f467dc1ded" } ,{ "testCaseDescription": "javascript-var-declaration-replacement-insert-test", @@ -111,9 +111,9 @@ "filePaths": [ "var-declaration.js" ], - "sha1": "64fc6fb51d210079cd9afabc5f566604f46e35ba", + "sha1": "eedc2942855b62115ad5dc3a6627b9f467dc1ded", "gitDir": "test/corpus/repos/javascript", - "sha2": "eab71c8144bb1445bb263d7d7dd6ba0f8728b047" + "sha2": "1257b186363ddaadbc39499f4bebd1fe1f4e386e" } ,{ "testCaseDescription": "javascript-var-declaration-delete-insert-test", @@ -191,9 +191,9 @@ "filePaths": [ "var-declaration.js" ], - "sha1": "eab71c8144bb1445bb263d7d7dd6ba0f8728b047", + "sha1": "1257b186363ddaadbc39499f4bebd1fe1f4e386e", "gitDir": "test/corpus/repos/javascript", - "sha2": "9ffe00e034939d94a0270d072e6cb6ab6fbce75a" + "sha2": "4bedf3cf2701ca07d66bb71eb8d2b4ac4f6b4833" } ,{ "testCaseDescription": "javascript-var-declaration-replacement-test", @@ -271,9 +271,9 @@ "filePaths": [ "var-declaration.js" ], - "sha1": "9ffe00e034939d94a0270d072e6cb6ab6fbce75a", + "sha1": "4bedf3cf2701ca07d66bb71eb8d2b4ac4f6b4833", "gitDir": "test/corpus/repos/javascript", - "sha2": "e82d5c901f5e471b3f531fd989751b7c5e797b66" + "sha2": "bf0dfe0114e3c9edb06bf246a532f5db0109214f" } ,{ "testCaseDescription": "javascript-var-declaration-delete-replacement-test", @@ -406,9 +406,9 @@ "filePaths": [ "var-declaration.js" ], - "sha1": "e82d5c901f5e471b3f531fd989751b7c5e797b66", + "sha1": "bf0dfe0114e3c9edb06bf246a532f5db0109214f", "gitDir": "test/corpus/repos/javascript", - "sha2": "35e9e019656681c243e258f38680af210ea248f3" + "sha2": "0b5297915a17bae22d13f9e86d866f6fa878225b" } ,{ "testCaseDescription": "javascript-var-declaration-delete-test", @@ -439,9 +439,9 @@ "filePaths": [ "var-declaration.js" ], - "sha1": "35e9e019656681c243e258f38680af210ea248f3", + "sha1": "0b5297915a17bae22d13f9e86d866f6fa878225b", "gitDir": "test/corpus/repos/javascript", - "sha2": "8e88238b5e011419977e6fa14d97be8d1c744002" + "sha2": "6890c55ff9c75b2fd4f29a20ac97707e57965ca1" } ,{ "testCaseDescription": "javascript-var-declaration-delete-rest-test", @@ -506,7 +506,7 @@ "filePaths": [ "var-declaration.js" ], - "sha1": "8e88238b5e011419977e6fa14d97be8d1c744002", + "sha1": "6890c55ff9c75b2fd4f29a20ac97707e57965ca1", "gitDir": "test/corpus/repos/javascript", - "sha2": "7c4be6139148ad009e9bf49df1952b9abe45aee0" + "sha2": "61540dc73cfaad0786519aca74727ab895384c00" }] diff --git a/test/corpus/diff-summaries/javascript/variable.json b/test/corpus/diff-summaries/javascript/variable.json index 3556124f7..ac8f5964f 100644 --- a/test/corpus/diff-summaries/javascript/variable.json +++ b/test/corpus/diff-summaries/javascript/variable.json @@ -27,9 +27,9 @@ "filePaths": [ "variable.js" ], - "sha1": "6539b8361c59312164d8321ca3888c0511fcf849", + "sha1": "76561264ab91701d52dcc8dcbb42c25ea412ae25", "gitDir": "test/corpus/repos/javascript", - "sha2": "c0e6c0ded2a3dced105d1ab80857cc20258b07ae" + "sha2": "677b66a442698673a2e039827f5259f4a618bdf6" } ,{ "testCaseDescription": "javascript-variable-replacement-insert-test", @@ -77,9 +77,9 @@ "filePaths": [ "variable.js" ], - "sha1": "c0e6c0ded2a3dced105d1ab80857cc20258b07ae", + "sha1": "677b66a442698673a2e039827f5259f4a618bdf6", "gitDir": "test/corpus/repos/javascript", - "sha2": "2de090754d832844bf03836c5e571ab5cad2e084" + "sha2": "7329fd9a1547c296931f6f4bf9ec680740a94429" } ,{ "testCaseDescription": "javascript-variable-delete-insert-test", @@ -123,9 +123,9 @@ "filePaths": [ "variable.js" ], - "sha1": "2de090754d832844bf03836c5e571ab5cad2e084", + "sha1": "7329fd9a1547c296931f6f4bf9ec680740a94429", "gitDir": "test/corpus/repos/javascript", - "sha2": "0f970d0d8f050af10bc4c12aaf36ffa4f13f8b2d" + "sha2": "8a8aa0a0874f8e702f3699af10a85abda3647742" } ,{ "testCaseDescription": "javascript-variable-replacement-test", @@ -169,9 +169,9 @@ "filePaths": [ "variable.js" ], - "sha1": "0f970d0d8f050af10bc4c12aaf36ffa4f13f8b2d", + "sha1": "8a8aa0a0874f8e702f3699af10a85abda3647742", "gitDir": "test/corpus/repos/javascript", - "sha2": "adf96a48ac5436cb72483251db0f21b1f6c0628e" + "sha2": "21de27cee9675fb27ed7fe0b27cc12ac59bb70fd" } ,{ "testCaseDescription": "javascript-variable-delete-replacement-test", @@ -236,9 +236,9 @@ "filePaths": [ "variable.js" ], - "sha1": "adf96a48ac5436cb72483251db0f21b1f6c0628e", + "sha1": "21de27cee9675fb27ed7fe0b27cc12ac59bb70fd", "gitDir": "test/corpus/repos/javascript", - "sha2": "51ba6b7b1c97e55fd7608918ac7bf9b5b4b986cd" + "sha2": "ac2b7f461f6de872b99447ea68b864915618c938" } ,{ "testCaseDescription": "javascript-variable-delete-test", @@ -269,9 +269,9 @@ "filePaths": [ "variable.js" ], - "sha1": "51ba6b7b1c97e55fd7608918ac7bf9b5b4b986cd", + "sha1": "ac2b7f461f6de872b99447ea68b864915618c938", "gitDir": "test/corpus/repos/javascript", - "sha2": "04b1ca5574c5256d2d3db1d073308ff0ce040736" + "sha2": "e517079aa213f18fcf8c0152222655a6ac3738cb" } ,{ "testCaseDescription": "javascript-variable-delete-rest-test", @@ -302,7 +302,7 @@ "filePaths": [ "variable.js" ], - "sha1": "04b1ca5574c5256d2d3db1d073308ff0ce040736", + "sha1": "e517079aa213f18fcf8c0152222655a6ac3738cb", "gitDir": "test/corpus/repos/javascript", - "sha2": "e8164f9a5c7441db5367d1dee13694204e67e3ab" + "sha2": "ea0156c09a6d9c183d037bddda50ce815c00548f" }] diff --git a/test/corpus/diff-summaries/javascript/void-operator.json b/test/corpus/diff-summaries/javascript/void-operator.json index e70464ca0..e2ec17ccc 100644 --- a/test/corpus/diff-summaries/javascript/void-operator.json +++ b/test/corpus/diff-summaries/javascript/void-operator.json @@ -27,9 +27,9 @@ "filePaths": [ "void-operator.js" ], - "sha1": "9b9215fdd0036d2a74bfc6a6c4b43187e3ad3ef8", + "sha1": "f8fceed82b3d3f5189fd21d8dd7a5589c803ba0e", "gitDir": "test/corpus/repos/javascript", - "sha2": "88f904cc009da2f43118249073884d11224bf555" + "sha2": "7998c6269fdd9a217d72c31e2a1f03fc53b0e8b5" } ,{ "testCaseDescription": "javascript-void-operator-replacement-insert-test", @@ -77,9 +77,9 @@ "filePaths": [ "void-operator.js" ], - "sha1": "88f904cc009da2f43118249073884d11224bf555", + "sha1": "7998c6269fdd9a217d72c31e2a1f03fc53b0e8b5", "gitDir": "test/corpus/repos/javascript", - "sha2": "65a805f7fe2111b798cc226fbf085c406fb00126" + "sha2": "1d89bdb5c21c95655bc123cde876265833d8ffc9" } ,{ "testCaseDescription": "javascript-void-operator-delete-insert-test", @@ -123,9 +123,9 @@ "filePaths": [ "void-operator.js" ], - "sha1": "65a805f7fe2111b798cc226fbf085c406fb00126", + "sha1": "1d89bdb5c21c95655bc123cde876265833d8ffc9", "gitDir": "test/corpus/repos/javascript", - "sha2": "f099f306c71ccab2f86105d2f2d9a9d1ce6211b7" + "sha2": "85960c0618449d02f5bd903400b67aaf2e2f3339" } ,{ "testCaseDescription": "javascript-void-operator-replacement-test", @@ -169,9 +169,9 @@ "filePaths": [ "void-operator.js" ], - "sha1": "f099f306c71ccab2f86105d2f2d9a9d1ce6211b7", + "sha1": "85960c0618449d02f5bd903400b67aaf2e2f3339", "gitDir": "test/corpus/repos/javascript", - "sha2": "c5c1f0f74dee37333fdd1202752d9bea669d1bcc" + "sha2": "9bbed4dcc43d4ecb67ce417bc49cd547eb5f0b84" } ,{ "testCaseDescription": "javascript-void-operator-delete-replacement-test", @@ -236,9 +236,9 @@ "filePaths": [ "void-operator.js" ], - "sha1": "c5c1f0f74dee37333fdd1202752d9bea669d1bcc", + "sha1": "9bbed4dcc43d4ecb67ce417bc49cd547eb5f0b84", "gitDir": "test/corpus/repos/javascript", - "sha2": "db4b02eb917d57894ba5712873b4cad0d5741cbc" + "sha2": "7ba4114b3c382854daad0d29360ec603919f3a8e" } ,{ "testCaseDescription": "javascript-void-operator-delete-test", @@ -269,9 +269,9 @@ "filePaths": [ "void-operator.js" ], - "sha1": "db4b02eb917d57894ba5712873b4cad0d5741cbc", + "sha1": "7ba4114b3c382854daad0d29360ec603919f3a8e", "gitDir": "test/corpus/repos/javascript", - "sha2": "b09908d0eaf50a489bab70fcd8a734a2553f97e8" + "sha2": "ec90e67790d2c3b9340ca93cf2d18fb2a51392f1" } ,{ "testCaseDescription": "javascript-void-operator-delete-rest-test", @@ -302,7 +302,7 @@ "filePaths": [ "void-operator.js" ], - "sha1": "b09908d0eaf50a489bab70fcd8a734a2553f97e8", + "sha1": "ec90e67790d2c3b9340ca93cf2d18fb2a51392f1", "gitDir": "test/corpus/repos/javascript", - "sha2": "7a5a7e14fdfb56a4dae67672a83aceb49d90f6bf" + "sha2": "5fc82ac3374f4c8d50af76e2ae299a59e4cff396" }] diff --git a/test/corpus/diff-summaries/javascript/while-statement.json b/test/corpus/diff-summaries/javascript/while-statement.json index 25f05e2eb..c9cad42d9 100644 --- a/test/corpus/diff-summaries/javascript/while-statement.json +++ b/test/corpus/diff-summaries/javascript/while-statement.json @@ -27,9 +27,9 @@ "filePaths": [ "while-statement.js" ], - "sha1": "1cbcc1b45ee2afdae4047efbc3ee0f15e89e3394", + "sha1": "536e58f01a1c35bfed654e16dc15d4b2636913b7", "gitDir": "test/corpus/repos/javascript", - "sha2": "274eacb4eff7e5773666228a9546e9ab1ec68774" + "sha2": "9fd0ed71c7fabfc6749ea3c9c9bee28325abff3d" } ,{ "testCaseDescription": "javascript-while-statement-replacement-insert-test", @@ -77,9 +77,9 @@ "filePaths": [ "while-statement.js" ], - "sha1": "274eacb4eff7e5773666228a9546e9ab1ec68774", + "sha1": "9fd0ed71c7fabfc6749ea3c9c9bee28325abff3d", "gitDir": "test/corpus/repos/javascript", - "sha2": "1b77e40e3f6486158c79f7acc346e102d8a78007" + "sha2": "b78d260ef2d0c3127aad32afc1cce7f94538c8b7" } ,{ "testCaseDescription": "javascript-while-statement-delete-insert-test", @@ -153,9 +153,9 @@ "filePaths": [ "while-statement.js" ], - "sha1": "1b77e40e3f6486158c79f7acc346e102d8a78007", + "sha1": "b78d260ef2d0c3127aad32afc1cce7f94538c8b7", "gitDir": "test/corpus/repos/javascript", - "sha2": "0eafdfad1e7720c217b9395c5b16d0e449914dbe" + "sha2": "399b7cbb6a6483291a0d018f1e2281a45361c7b1" } ,{ "testCaseDescription": "javascript-while-statement-replacement-test", @@ -229,9 +229,9 @@ "filePaths": [ "while-statement.js" ], - "sha1": "0eafdfad1e7720c217b9395c5b16d0e449914dbe", + "sha1": "399b7cbb6a6483291a0d018f1e2281a45361c7b1", "gitDir": "test/corpus/repos/javascript", - "sha2": "31f8024c950f170297ffddb0f3d7b0b215c4e21f" + "sha2": "a01f0234b0944a97f30e87e74475f16104ba25e6" } ,{ "testCaseDescription": "javascript-while-statement-delete-replacement-test", @@ -296,9 +296,9 @@ "filePaths": [ "while-statement.js" ], - "sha1": "31f8024c950f170297ffddb0f3d7b0b215c4e21f", + "sha1": "a01f0234b0944a97f30e87e74475f16104ba25e6", "gitDir": "test/corpus/repos/javascript", - "sha2": "70bf5f2b28fde7bd03a50ad40833c344aec3f10a" + "sha2": "775cc5eeed82a76131e5dff1a794fc408ad42f32" } ,{ "testCaseDescription": "javascript-while-statement-delete-test", @@ -329,9 +329,9 @@ "filePaths": [ "while-statement.js" ], - "sha1": "70bf5f2b28fde7bd03a50ad40833c344aec3f10a", + "sha1": "775cc5eeed82a76131e5dff1a794fc408ad42f32", "gitDir": "test/corpus/repos/javascript", - "sha2": "2e362f8f0146680a3f4c3d5221130d532926b308" + "sha2": "7fac6925a6d8770e05a062fcf60f512e2fc6a866" } ,{ "testCaseDescription": "javascript-while-statement-delete-rest-test", @@ -362,7 +362,7 @@ "filePaths": [ "while-statement.js" ], - "sha1": "2e362f8f0146680a3f4c3d5221130d532926b308", + "sha1": "7fac6925a6d8770e05a062fcf60f512e2fc6a866", "gitDir": "test/corpus/repos/javascript", - "sha2": "101c947313c24c2e76769c572c080adea44c80da" + "sha2": "ea67bdfe9d16bfb0ba0858898f969294740b84fb" }] diff --git a/test/corpus/repos/javascript b/test/corpus/repos/javascript index f7d88a07b..215d10e67 160000 --- a/test/corpus/repos/javascript +++ b/test/corpus/repos/javascript @@ -1 +1 @@ -Subproject commit f7d88a07b742fd7334d28806f01764ddfed94384 +Subproject commit 215d10e67e03c8e29f188758043ace6b619b01e5 From 70d39544cbd3339877d782624855bb8508641280 Mon Sep 17 00:00:00 2001 From: joshvera Date: Tue, 11 Oct 2016 12:46:40 -0400 Subject: [PATCH 21/27] Rename to filepath --- src/SourceSpan.hs | 8 ++++---- 1 file changed, 4 insertions(+), 4 deletions(-) diff --git a/src/SourceSpan.hs b/src/SourceSpan.hs index 0c6625a94..040de09c0 100644 --- a/src/SourceSpan.hs +++ b/src/SourceSpan.hs @@ -63,15 +63,15 @@ displaySourceSpan sp = instance A.ToJSON SourceSpan where toJSON SourceSpan{..} = - A.object [ "name" .= spanName + A.object [ "filepath" .= spanName , "start" .= spanStart - , "end" .= spanEnd + , "end" .= spanEnd ] instance A.FromJSON SourceSpan where parseJSON = A.withObject "SourceSpan" $ \o -> - SourceSpan <$> - o .: "name" <*> + SourceSpan <$> + o .: "filepath" <*> o .: "start" <*> o .: "end" From e57c80940ea770a878d91007847247e754b3863f Mon Sep 17 00:00:00 2001 From: joshvera Date: Tue, 11 Oct 2016 12:52:26 -0400 Subject: [PATCH 22/27] bump tests --- .../javascript/anonymous-function.json | 76 +++++++-------- .../anonymous-parameterless-function.json | 52 +++++------ .../diff-summaries/javascript/array.json | 48 +++++----- .../javascript/arrow-function.json | 52 +++++------ .../diff-summaries/javascript/assignment.json | 52 +++++------ .../javascript/bitwise-operator.json | 52 +++++------ .../javascript/boolean-operator.json | 40 ++++---- .../javascript/chained-callbacks.json | 68 +++++++------- .../javascript/chained-property-access.json | 60 ++++++------ .../diff-summaries/javascript/class.json | 68 +++++++------- .../javascript/comma-operator.json | 64 ++++++------- .../diff-summaries/javascript/comment.json | 52 +++++------ .../javascript/constructor-call.json | 52 +++++------ .../javascript/delete-operator.json | 52 +++++------ .../javascript/do-while-statement.json | 60 ++++++------ .../diff-summaries/javascript/false.json | 52 +++++------ .../javascript/for-in-statement.json | 68 +++++++------- .../for-loop-with-in-statement.json | 60 ++++++------ .../javascript/for-of-statement.json | 68 +++++++------- .../javascript/for-statement.json | 52 +++++------ .../javascript/function-call-args.json | 92 +++++++++---------- .../javascript/function-call.json | 52 +++++------ .../diff-summaries/javascript/function.json | 52 +++++------ .../javascript/generator-function.json | 52 +++++------ .../diff-summaries/javascript/identifier.json | 52 +++++------ .../diff-summaries/javascript/if-else.json | 52 +++++------ test/corpus/diff-summaries/javascript/if.json | 52 +++++------ .../javascript/math-assignment-operator.json | 52 +++++------ .../javascript/math-operator.json | 60 ++++++------ .../javascript/member-access-assignment.json | 52 +++++------ .../javascript/member-access.json | 52 +++++------ .../javascript/method-call.json | 52 +++++------ .../javascript/named-function.json | 68 +++++++------- .../javascript/nested-functions.json | 60 ++++++------ .../diff-summaries/javascript/null.json | 52 +++++------ .../diff-summaries/javascript/number.json | 52 +++++------ .../javascript/object-with-methods.json | 52 +++++------ .../diff-summaries/javascript/object.json | 52 +++++------ .../diff-summaries/javascript/regex.json | 52 +++++------ .../javascript/relational-operator.json | 40 ++++---- .../javascript/return-statement.json | 48 +++++----- .../diff-summaries/javascript/string.json | 52 +++++------ .../subscript-access-assignment.json | 52 +++++------ .../javascript/subscript-access-string.json | 52 +++++------ .../javascript/subscript-access-variable.json | 52 +++++------ .../javascript/switch-statement.json | 60 ++++++------ .../javascript/template-string.json | 52 +++++------ .../diff-summaries/javascript/ternary.json | 52 +++++------ .../javascript/this-expression.json | 52 +++++------ .../javascript/throw-statement.json | 52 +++++------ .../diff-summaries/javascript/true.json | 52 +++++------ .../javascript/try-statement.json | 60 ++++++------ .../javascript/type-operator.json | 48 +++++----- .../diff-summaries/javascript/undefined.json | 52 +++++------ .../javascript/var-declaration.json | 76 +++++++-------- .../diff-summaries/javascript/variable.json | 52 +++++------ .../javascript/void-operator.json | 52 +++++------ .../javascript/while-statement.json | 60 ++++++------ test/corpus/repos/javascript | 2 +- 59 files changed, 1613 insertions(+), 1613 deletions(-) diff --git a/test/corpus/diff-summaries/javascript/anonymous-function.json b/test/corpus/diff-summaries/javascript/anonymous-function.json index c2d795c01..966e2699b 100644 --- a/test/corpus/diff-summaries/javascript/anonymous-function.json +++ b/test/corpus/diff-summaries/javascript/anonymous-function.json @@ -10,7 +10,7 @@ 1, 1 ], - "name": "anonymous-function.js", + "filepath": "anonymous-function.js", "end": [ 1, 32 @@ -27,9 +27,9 @@ "filePaths": [ "anonymous-function.js" ], - "sha1": "804f2056b155a51e98aacc2af9f2950bab4cbaf8", + "sha1": "458495ca9be4e43e96aed296de34fe136605b436", "gitDir": "test/corpus/repos/javascript", - "sha2": "eda4f0da16edab81e68fa4bd40bdf68317bf4a75" + "sha2": "027500f42df1cb82966a8eacc5a612e396e4b53d" } ,{ "testCaseDescription": "javascript-anonymous-function-replacement-insert-test", @@ -43,7 +43,7 @@ 1, 1 ], - "name": "anonymous-function.js", + "filepath": "anonymous-function.js", "end": [ 1, 32 @@ -60,7 +60,7 @@ 2, 1 ], - "name": "anonymous-function.js", + "filepath": "anonymous-function.js", "end": [ 2, 32 @@ -77,9 +77,9 @@ "filePaths": [ "anonymous-function.js" ], - "sha1": "eda4f0da16edab81e68fa4bd40bdf68317bf4a75", + "sha1": "027500f42df1cb82966a8eacc5a612e396e4b53d", "gitDir": "test/corpus/repos/javascript", - "sha2": "319f65e34cfba43aa61e6e58594d3e4cb4d21be2" + "sha2": "fa10f745f2b6e09744a5213a919a5bfd934a4e72" } ,{ "testCaseDescription": "javascript-anonymous-function-delete-insert-test", @@ -94,7 +94,7 @@ 1, 10 ], - "name": "anonymous-function.js", + "filepath": "anonymous-function.js", "end": [ 1, 11 @@ -105,7 +105,7 @@ 1, 10 ], - "name": "anonymous-function.js", + "filepath": "anonymous-function.js", "end": [ 1, 11 @@ -124,7 +124,7 @@ 1, 12 ], - "name": "anonymous-function.js", + "filepath": "anonymous-function.js", "end": [ 1, 13 @@ -135,7 +135,7 @@ 1, 12 ], - "name": "anonymous-function.js", + "filepath": "anonymous-function.js", "end": [ 1, 13 @@ -154,7 +154,7 @@ 1, 24 ], - "name": "anonymous-function.js", + "filepath": "anonymous-function.js", "end": [ 1, 25 @@ -165,7 +165,7 @@ 1, 24 ], - "name": "anonymous-function.js", + "filepath": "anonymous-function.js", "end": [ 1, 25 @@ -184,7 +184,7 @@ 1, 28 ], - "name": "anonymous-function.js", + "filepath": "anonymous-function.js", "end": [ 1, 29 @@ -195,7 +195,7 @@ 1, 28 ], - "name": "anonymous-function.js", + "filepath": "anonymous-function.js", "end": [ 1, 29 @@ -213,9 +213,9 @@ "filePaths": [ "anonymous-function.js" ], - "sha1": "319f65e34cfba43aa61e6e58594d3e4cb4d21be2", + "sha1": "fa10f745f2b6e09744a5213a919a5bfd934a4e72", "gitDir": "test/corpus/repos/javascript", - "sha2": "ca9fb83ac14937adeac12170c6faf20798086a2c" + "sha2": "65004040936dd5a6dc031dbc2face4db2d609d48" } ,{ "testCaseDescription": "javascript-anonymous-function-replacement-test", @@ -230,7 +230,7 @@ 1, 10 ], - "name": "anonymous-function.js", + "filepath": "anonymous-function.js", "end": [ 1, 11 @@ -241,7 +241,7 @@ 1, 10 ], - "name": "anonymous-function.js", + "filepath": "anonymous-function.js", "end": [ 1, 11 @@ -260,7 +260,7 @@ 1, 12 ], - "name": "anonymous-function.js", + "filepath": "anonymous-function.js", "end": [ 1, 13 @@ -271,7 +271,7 @@ 1, 12 ], - "name": "anonymous-function.js", + "filepath": "anonymous-function.js", "end": [ 1, 13 @@ -290,7 +290,7 @@ 1, 24 ], - "name": "anonymous-function.js", + "filepath": "anonymous-function.js", "end": [ 1, 25 @@ -301,7 +301,7 @@ 1, 24 ], - "name": "anonymous-function.js", + "filepath": "anonymous-function.js", "end": [ 1, 25 @@ -320,7 +320,7 @@ 1, 28 ], - "name": "anonymous-function.js", + "filepath": "anonymous-function.js", "end": [ 1, 29 @@ -331,7 +331,7 @@ 1, 28 ], - "name": "anonymous-function.js", + "filepath": "anonymous-function.js", "end": [ 1, 29 @@ -349,9 +349,9 @@ "filePaths": [ "anonymous-function.js" ], - "sha1": "ca9fb83ac14937adeac12170c6faf20798086a2c", + "sha1": "65004040936dd5a6dc031dbc2face4db2d609d48", "gitDir": "test/corpus/repos/javascript", - "sha2": "3dc91ac24280fa629998c616530cd3310d6955a6" + "sha2": "a62e5f87aa64e61cca7ade935b9042969b562257" } ,{ "testCaseDescription": "javascript-anonymous-function-delete-replacement-test", @@ -365,7 +365,7 @@ 1, 1 ], - "name": "anonymous-function.js", + "filepath": "anonymous-function.js", "end": [ 1, 32 @@ -382,7 +382,7 @@ 2, 1 ], - "name": "anonymous-function.js", + "filepath": "anonymous-function.js", "end": [ 2, 32 @@ -399,7 +399,7 @@ 2, 1 ], - "name": "anonymous-function.js", + "filepath": "anonymous-function.js", "end": [ 2, 32 @@ -416,9 +416,9 @@ "filePaths": [ "anonymous-function.js" ], - "sha1": "3dc91ac24280fa629998c616530cd3310d6955a6", + "sha1": "a62e5f87aa64e61cca7ade935b9042969b562257", "gitDir": "test/corpus/repos/javascript", - "sha2": "9751610debe4f24e742ec7ffa6abe965144c8345" + "sha2": "7e92308c517833b045c6107fc999a8c6d4858551" } ,{ "testCaseDescription": "javascript-anonymous-function-delete-test", @@ -432,7 +432,7 @@ 1, 1 ], - "name": "anonymous-function.js", + "filepath": "anonymous-function.js", "end": [ 1, 32 @@ -449,9 +449,9 @@ "filePaths": [ "anonymous-function.js" ], - "sha1": "9751610debe4f24e742ec7ffa6abe965144c8345", + "sha1": "7e92308c517833b045c6107fc999a8c6d4858551", "gitDir": "test/corpus/repos/javascript", - "sha2": "962e9daa6bd0b7ec868e454f11d5aa3b6b1c4424" + "sha2": "d74a906e343cf2f938581b92a17863d90f66d7b1" } ,{ "testCaseDescription": "javascript-anonymous-function-delete-rest-test", @@ -465,7 +465,7 @@ 1, 1 ], - "name": "anonymous-function.js", + "filepath": "anonymous-function.js", "end": [ 1, 32 @@ -482,7 +482,7 @@ "filePaths": [ "anonymous-function.js" ], - "sha1": "962e9daa6bd0b7ec868e454f11d5aa3b6b1c4424", + "sha1": "d74a906e343cf2f938581b92a17863d90f66d7b1", "gitDir": "test/corpus/repos/javascript", - "sha2": "7a7a8f4f58f05a4dcfb46eb314604dfd141d6d2c" + "sha2": "57e6cad9cbe4a2a75bde2d8757af93d7f6a873ad" }] diff --git a/test/corpus/diff-summaries/javascript/anonymous-parameterless-function.json b/test/corpus/diff-summaries/javascript/anonymous-parameterless-function.json index d7918307f..34033d8cf 100644 --- a/test/corpus/diff-summaries/javascript/anonymous-parameterless-function.json +++ b/test/corpus/diff-summaries/javascript/anonymous-parameterless-function.json @@ -10,7 +10,7 @@ 1, 1 ], - "name": "anonymous-parameterless-function.js", + "filepath": "anonymous-parameterless-function.js", "end": [ 1, 28 @@ -27,9 +27,9 @@ "filePaths": [ "anonymous-parameterless-function.js" ], - "sha1": "7a7a8f4f58f05a4dcfb46eb314604dfd141d6d2c", + "sha1": "d14d8cc93f702b58a34b96956efc55af88d7da49", "gitDir": "test/corpus/repos/javascript", - "sha2": "d42d2dbcaf69d5ac4a623c4857f1654275987a45" + "sha2": "8455c6e817638d5fe75d43f553582555232674e7" } ,{ "testCaseDescription": "javascript-anonymous-parameterless-function-replacement-insert-test", @@ -43,7 +43,7 @@ 1, 1 ], - "name": "anonymous-parameterless-function.js", + "filepath": "anonymous-parameterless-function.js", "end": [ 1, 31 @@ -60,7 +60,7 @@ 2, 1 ], - "name": "anonymous-parameterless-function.js", + "filepath": "anonymous-parameterless-function.js", "end": [ 2, 28 @@ -77,9 +77,9 @@ "filePaths": [ "anonymous-parameterless-function.js" ], - "sha1": "d42d2dbcaf69d5ac4a623c4857f1654275987a45", + "sha1": "8455c6e817638d5fe75d43f553582555232674e7", "gitDir": "test/corpus/repos/javascript", - "sha2": "064b910da3162d2be95198714ff8eeb6057b1cab" + "sha2": "a6a831bf5c9b2fa9190f81f451c16a78efa9e99f" } ,{ "testCaseDescription": "javascript-anonymous-parameterless-function-delete-insert-test", @@ -94,7 +94,7 @@ 1, 21 ], - "name": "anonymous-parameterless-function.js", + "filepath": "anonymous-parameterless-function.js", "end": [ 1, 28 @@ -105,7 +105,7 @@ 1, 21 ], - "name": "anonymous-parameterless-function.js", + "filepath": "anonymous-parameterless-function.js", "end": [ 1, 25 @@ -123,9 +123,9 @@ "filePaths": [ "anonymous-parameterless-function.js" ], - "sha1": "064b910da3162d2be95198714ff8eeb6057b1cab", + "sha1": "a6a831bf5c9b2fa9190f81f451c16a78efa9e99f", "gitDir": "test/corpus/repos/javascript", - "sha2": "900df08eb69e5ec7cf0935f834dff84d2a8f938d" + "sha2": "2804e11f703d7790f92d9f55e090ebe242ef5b72" } ,{ "testCaseDescription": "javascript-anonymous-parameterless-function-replacement-test", @@ -140,7 +140,7 @@ 1, 21 ], - "name": "anonymous-parameterless-function.js", + "filepath": "anonymous-parameterless-function.js", "end": [ 1, 25 @@ -151,7 +151,7 @@ 1, 21 ], - "name": "anonymous-parameterless-function.js", + "filepath": "anonymous-parameterless-function.js", "end": [ 1, 28 @@ -169,9 +169,9 @@ "filePaths": [ "anonymous-parameterless-function.js" ], - "sha1": "900df08eb69e5ec7cf0935f834dff84d2a8f938d", + "sha1": "2804e11f703d7790f92d9f55e090ebe242ef5b72", "gitDir": "test/corpus/repos/javascript", - "sha2": "0dee59c204e74e8e797b0acf9295c5c13b3be400" + "sha2": "c40b9ac616e854e2afbc648539756919da040482" } ,{ "testCaseDescription": "javascript-anonymous-parameterless-function-delete-replacement-test", @@ -185,7 +185,7 @@ 1, 1 ], - "name": "anonymous-parameterless-function.js", + "filepath": "anonymous-parameterless-function.js", "end": [ 1, 31 @@ -202,7 +202,7 @@ 2, 1 ], - "name": "anonymous-parameterless-function.js", + "filepath": "anonymous-parameterless-function.js", "end": [ 2, 28 @@ -219,7 +219,7 @@ 2, 1 ], - "name": "anonymous-parameterless-function.js", + "filepath": "anonymous-parameterless-function.js", "end": [ 2, 31 @@ -236,9 +236,9 @@ "filePaths": [ "anonymous-parameterless-function.js" ], - "sha1": "0dee59c204e74e8e797b0acf9295c5c13b3be400", + "sha1": "c40b9ac616e854e2afbc648539756919da040482", "gitDir": "test/corpus/repos/javascript", - "sha2": "afd1bced812dcd0391498cd66d5392edeb3a6857" + "sha2": "2b3bea05ea9bfd348af449fe6d501b0b34ad6622" } ,{ "testCaseDescription": "javascript-anonymous-parameterless-function-delete-test", @@ -252,7 +252,7 @@ 1, 1 ], - "name": "anonymous-parameterless-function.js", + "filepath": "anonymous-parameterless-function.js", "end": [ 1, 28 @@ -269,9 +269,9 @@ "filePaths": [ "anonymous-parameterless-function.js" ], - "sha1": "afd1bced812dcd0391498cd66d5392edeb3a6857", + "sha1": "2b3bea05ea9bfd348af449fe6d501b0b34ad6622", "gitDir": "test/corpus/repos/javascript", - "sha2": "088434491f81994ef21a56a8e814f4c82af996b2" + "sha2": "e18bf99e350a1878b39e388b2b4a72ad1b67810f" } ,{ "testCaseDescription": "javascript-anonymous-parameterless-function-delete-rest-test", @@ -285,7 +285,7 @@ 1, 1 ], - "name": "anonymous-parameterless-function.js", + "filepath": "anonymous-parameterless-function.js", "end": [ 1, 31 @@ -302,7 +302,7 @@ "filePaths": [ "anonymous-parameterless-function.js" ], - "sha1": "088434491f81994ef21a56a8e814f4c82af996b2", + "sha1": "e18bf99e350a1878b39e388b2b4a72ad1b67810f", "gitDir": "test/corpus/repos/javascript", - "sha2": "2a302d002490d7bb5aff372747a028cec52c1b4b" + "sha2": "0963a5f0b33f11cb6d249be215092b7f5cbd1e1a" }] diff --git a/test/corpus/diff-summaries/javascript/array.json b/test/corpus/diff-summaries/javascript/array.json index f2c4336a7..20ea6f3e1 100644 --- a/test/corpus/diff-summaries/javascript/array.json +++ b/test/corpus/diff-summaries/javascript/array.json @@ -10,7 +10,7 @@ 1, 1 ], - "name": "array.js", + "filepath": "array.js", "end": [ 1, 12 @@ -27,9 +27,9 @@ "filePaths": [ "array.js" ], - "sha1": "04b681e1190310f6148595f3d80260ae13299d43", + "sha1": "17086d6403b7d2b299f9fb62681b786baee0e6bd", "gitDir": "test/corpus/repos/javascript", - "sha2": "f764a79ec733a7f8fd0cb4016f918b2eefa89b51" + "sha2": "1acecd849e5ebb797243d4ab053d43a9f249ec75" } ,{ "testCaseDescription": "javascript-array-replacement-insert-test", @@ -43,7 +43,7 @@ 1, 1 ], - "name": "array.js", + "filepath": "array.js", "end": [ 1, 21 @@ -60,7 +60,7 @@ 2, 1 ], - "name": "array.js", + "filepath": "array.js", "end": [ 2, 12 @@ -77,9 +77,9 @@ "filePaths": [ "array.js" ], - "sha1": "f764a79ec733a7f8fd0cb4016f918b2eefa89b51", + "sha1": "1acecd849e5ebb797243d4ab053d43a9f249ec75", "gitDir": "test/corpus/repos/javascript", - "sha2": "5a2f8c9043ef76d04634f22dd120f3c950711887" + "sha2": "8ec642fbb15429c3bad4ce7fcbc8e539ad0b669f" } ,{ "testCaseDescription": "javascript-array-delete-insert-test", @@ -93,7 +93,7 @@ 1, 12 ], - "name": "array.js", + "filepath": "array.js", "end": [ 1, 19 @@ -110,9 +110,9 @@ "filePaths": [ "array.js" ], - "sha1": "5a2f8c9043ef76d04634f22dd120f3c950711887", + "sha1": "8ec642fbb15429c3bad4ce7fcbc8e539ad0b669f", "gitDir": "test/corpus/repos/javascript", - "sha2": "5c1725c772ad618a734f78ba80bc29990a06f8a1" + "sha2": "e53fecade391ea96be94a251b3ec03790a63b71b" } ,{ "testCaseDescription": "javascript-array-replacement-test", @@ -126,7 +126,7 @@ 1, 12 ], - "name": "array.js", + "filepath": "array.js", "end": [ 1, 19 @@ -143,9 +143,9 @@ "filePaths": [ "array.js" ], - "sha1": "5c1725c772ad618a734f78ba80bc29990a06f8a1", + "sha1": "e53fecade391ea96be94a251b3ec03790a63b71b", "gitDir": "test/corpus/repos/javascript", - "sha2": "779013762c7bcb016f2ec80ab3caed4384fc4113" + "sha2": "c5882f5220ba2b16310ee4fb99aa13ee2daa1c31" } ,{ "testCaseDescription": "javascript-array-delete-replacement-test", @@ -159,7 +159,7 @@ 1, 1 ], - "name": "array.js", + "filepath": "array.js", "end": [ 1, 21 @@ -176,7 +176,7 @@ 2, 1 ], - "name": "array.js", + "filepath": "array.js", "end": [ 2, 12 @@ -193,7 +193,7 @@ 2, 1 ], - "name": "array.js", + "filepath": "array.js", "end": [ 2, 21 @@ -210,9 +210,9 @@ "filePaths": [ "array.js" ], - "sha1": "779013762c7bcb016f2ec80ab3caed4384fc4113", + "sha1": "c5882f5220ba2b16310ee4fb99aa13ee2daa1c31", "gitDir": "test/corpus/repos/javascript", - "sha2": "daf668c7bbccb5e2a70cd5e6d081ea35dfddb879" + "sha2": "d8513ea06d23b115c1d4414eebe84bed39b3eb8e" } ,{ "testCaseDescription": "javascript-array-delete-test", @@ -226,7 +226,7 @@ 1, 1 ], - "name": "array.js", + "filepath": "array.js", "end": [ 1, 12 @@ -243,9 +243,9 @@ "filePaths": [ "array.js" ], - "sha1": "daf668c7bbccb5e2a70cd5e6d081ea35dfddb879", + "sha1": "d8513ea06d23b115c1d4414eebe84bed39b3eb8e", "gitDir": "test/corpus/repos/javascript", - "sha2": "6e471401fdfac17a93fa8e5fb87924864dd4b07b" + "sha2": "6170bb216fc1ced5e9707690e5bbf8a63b33d593" } ,{ "testCaseDescription": "javascript-array-delete-rest-test", @@ -259,7 +259,7 @@ 1, 1 ], - "name": "array.js", + "filepath": "array.js", "end": [ 1, 21 @@ -276,7 +276,7 @@ "filePaths": [ "array.js" ], - "sha1": "6e471401fdfac17a93fa8e5fb87924864dd4b07b", + "sha1": "6170bb216fc1ced5e9707690e5bbf8a63b33d593", "gitDir": "test/corpus/repos/javascript", - "sha2": "0921c7be9afb30bdf6fa3861d12c20a87ae67736" + "sha2": "b391c180ba171aa1ebfe29dde8a2d4a9caa09424" }] diff --git a/test/corpus/diff-summaries/javascript/arrow-function.json b/test/corpus/diff-summaries/javascript/arrow-function.json index 220d8100d..ac9bcb99f 100644 --- a/test/corpus/diff-summaries/javascript/arrow-function.json +++ b/test/corpus/diff-summaries/javascript/arrow-function.json @@ -10,7 +10,7 @@ 1, 1 ], - "name": "arrow-function.js", + "filepath": "arrow-function.js", "end": [ 1, 24 @@ -27,9 +27,9 @@ "filePaths": [ "arrow-function.js" ], - "sha1": "2327a0433e3123ddf19226ee5172c928f24b3af1", + "sha1": "6fefc420e9dab913a39b8bced7330b7517983783", "gitDir": "test/corpus/repos/javascript", - "sha2": "fb18e7576ad5e8c1f6007ec75e366d78c401fcc8" + "sha2": "f3749a22cb857f90b24414206c13ebd892a9d5f6" } ,{ "testCaseDescription": "javascript-arrow-function-replacement-insert-test", @@ -43,7 +43,7 @@ 1, 1 ], - "name": "arrow-function.js", + "filepath": "arrow-function.js", "end": [ 1, 24 @@ -60,7 +60,7 @@ 2, 1 ], - "name": "arrow-function.js", + "filepath": "arrow-function.js", "end": [ 2, 24 @@ -77,9 +77,9 @@ "filePaths": [ "arrow-function.js" ], - "sha1": "fb18e7576ad5e8c1f6007ec75e366d78c401fcc8", + "sha1": "f3749a22cb857f90b24414206c13ebd892a9d5f6", "gitDir": "test/corpus/repos/javascript", - "sha2": "140eb10dce63b1e9b8edd202efdf5ede1cfee31f" + "sha2": "673be97dc46351ade1e3e53baa02f4992bb910e0" } ,{ "testCaseDescription": "javascript-arrow-function-delete-insert-test", @@ -94,7 +94,7 @@ 1, 20 ], - "name": "arrow-function.js", + "filepath": "arrow-function.js", "end": [ 1, 21 @@ -105,7 +105,7 @@ 1, 20 ], - "name": "arrow-function.js", + "filepath": "arrow-function.js", "end": [ 1, 21 @@ -123,9 +123,9 @@ "filePaths": [ "arrow-function.js" ], - "sha1": "140eb10dce63b1e9b8edd202efdf5ede1cfee31f", + "sha1": "673be97dc46351ade1e3e53baa02f4992bb910e0", "gitDir": "test/corpus/repos/javascript", - "sha2": "38800991dd39be51410c9a4cd97f0b5ca90ec95d" + "sha2": "0c2b12501c2a62eecf66de9f955d544e8f613ea1" } ,{ "testCaseDescription": "javascript-arrow-function-replacement-test", @@ -140,7 +140,7 @@ 1, 20 ], - "name": "arrow-function.js", + "filepath": "arrow-function.js", "end": [ 1, 21 @@ -151,7 +151,7 @@ 1, 20 ], - "name": "arrow-function.js", + "filepath": "arrow-function.js", "end": [ 1, 21 @@ -169,9 +169,9 @@ "filePaths": [ "arrow-function.js" ], - "sha1": "38800991dd39be51410c9a4cd97f0b5ca90ec95d", + "sha1": "0c2b12501c2a62eecf66de9f955d544e8f613ea1", "gitDir": "test/corpus/repos/javascript", - "sha2": "cda2aefb00dc0c425737770e5d0f71d2952dc41c" + "sha2": "48faa11201679fa823f2dd3bae167656b3172df6" } ,{ "testCaseDescription": "javascript-arrow-function-delete-replacement-test", @@ -185,7 +185,7 @@ 1, 1 ], - "name": "arrow-function.js", + "filepath": "arrow-function.js", "end": [ 1, 24 @@ -202,7 +202,7 @@ 2, 1 ], - "name": "arrow-function.js", + "filepath": "arrow-function.js", "end": [ 2, 24 @@ -219,7 +219,7 @@ 2, 1 ], - "name": "arrow-function.js", + "filepath": "arrow-function.js", "end": [ 2, 24 @@ -236,9 +236,9 @@ "filePaths": [ "arrow-function.js" ], - "sha1": "cda2aefb00dc0c425737770e5d0f71d2952dc41c", + "sha1": "48faa11201679fa823f2dd3bae167656b3172df6", "gitDir": "test/corpus/repos/javascript", - "sha2": "09183e7e67ff885a3eb4d9cc48700496f93274c6" + "sha2": "2966cb10717ee4fb395ca159270e923b146141b0" } ,{ "testCaseDescription": "javascript-arrow-function-delete-test", @@ -252,7 +252,7 @@ 1, 1 ], - "name": "arrow-function.js", + "filepath": "arrow-function.js", "end": [ 1, 24 @@ -269,9 +269,9 @@ "filePaths": [ "arrow-function.js" ], - "sha1": "09183e7e67ff885a3eb4d9cc48700496f93274c6", + "sha1": "2966cb10717ee4fb395ca159270e923b146141b0", "gitDir": "test/corpus/repos/javascript", - "sha2": "a36d1e0f9a73f7a5f4fff31fb53773484b26f1b3" + "sha2": "3e18962fcb8f406c83ccd299db2142abae785843" } ,{ "testCaseDescription": "javascript-arrow-function-delete-rest-test", @@ -285,7 +285,7 @@ 1, 1 ], - "name": "arrow-function.js", + "filepath": "arrow-function.js", "end": [ 1, 24 @@ -302,7 +302,7 @@ "filePaths": [ "arrow-function.js" ], - "sha1": "a36d1e0f9a73f7a5f4fff31fb53773484b26f1b3", + "sha1": "3e18962fcb8f406c83ccd299db2142abae785843", "gitDir": "test/corpus/repos/javascript", - "sha2": "dcaa57653ecd13d885de551a47032d37ef10e47e" + "sha2": "7b09010913796d6d4fa1dd7e3dc0d600b126f461" }] diff --git a/test/corpus/diff-summaries/javascript/assignment.json b/test/corpus/diff-summaries/javascript/assignment.json index f20474fab..4b27687ba 100644 --- a/test/corpus/diff-summaries/javascript/assignment.json +++ b/test/corpus/diff-summaries/javascript/assignment.json @@ -10,7 +10,7 @@ 1, 1 ], - "name": "assignment.js", + "filepath": "assignment.js", "end": [ 1, 6 @@ -27,9 +27,9 @@ "filePaths": [ "assignment.js" ], - "sha1": "7c328351e5e8debb38b46a45f43481581e438666", + "sha1": "c0a27778617b5784aa85473904bc5c324a3301b2", "gitDir": "test/corpus/repos/javascript", - "sha2": "6ba03898f9fd18c886831a602180fad0fc468e31" + "sha2": "8ff4b0ad88cc00944bb57ec7f45be4d31ef0b518" } ,{ "testCaseDescription": "javascript-assignment-replacement-insert-test", @@ -43,7 +43,7 @@ 1, 1 ], - "name": "assignment.js", + "filepath": "assignment.js", "end": [ 1, 6 @@ -60,7 +60,7 @@ 2, 1 ], - "name": "assignment.js", + "filepath": "assignment.js", "end": [ 2, 6 @@ -77,9 +77,9 @@ "filePaths": [ "assignment.js" ], - "sha1": "6ba03898f9fd18c886831a602180fad0fc468e31", + "sha1": "8ff4b0ad88cc00944bb57ec7f45be4d31ef0b518", "gitDir": "test/corpus/repos/javascript", - "sha2": "f70ee402927b75eeae9a6d38d4da7c130dda80e0" + "sha2": "3c66031a52c2c3b9db42518f1ecbf5c625fb7c42" } ,{ "testCaseDescription": "javascript-assignment-delete-insert-test", @@ -94,7 +94,7 @@ 1, 5 ], - "name": "assignment.js", + "filepath": "assignment.js", "end": [ 1, 6 @@ -105,7 +105,7 @@ 1, 5 ], - "name": "assignment.js", + "filepath": "assignment.js", "end": [ 1, 6 @@ -123,9 +123,9 @@ "filePaths": [ "assignment.js" ], - "sha1": "f70ee402927b75eeae9a6d38d4da7c130dda80e0", + "sha1": "3c66031a52c2c3b9db42518f1ecbf5c625fb7c42", "gitDir": "test/corpus/repos/javascript", - "sha2": "98be0baf2ee4ad6d59621872395016241d9dd66e" + "sha2": "8d1a55aa2be800b18ae460af412673ef66b969e2" } ,{ "testCaseDescription": "javascript-assignment-replacement-test", @@ -140,7 +140,7 @@ 1, 5 ], - "name": "assignment.js", + "filepath": "assignment.js", "end": [ 1, 6 @@ -151,7 +151,7 @@ 1, 5 ], - "name": "assignment.js", + "filepath": "assignment.js", "end": [ 1, 6 @@ -169,9 +169,9 @@ "filePaths": [ "assignment.js" ], - "sha1": "98be0baf2ee4ad6d59621872395016241d9dd66e", + "sha1": "8d1a55aa2be800b18ae460af412673ef66b969e2", "gitDir": "test/corpus/repos/javascript", - "sha2": "53d0889371bf94bcfac80d7650321255b41eeb38" + "sha2": "f509f4afce54da5e15cbd2fe7db4d9f085618bdb" } ,{ "testCaseDescription": "javascript-assignment-delete-replacement-test", @@ -185,7 +185,7 @@ 1, 1 ], - "name": "assignment.js", + "filepath": "assignment.js", "end": [ 1, 6 @@ -202,7 +202,7 @@ 2, 1 ], - "name": "assignment.js", + "filepath": "assignment.js", "end": [ 2, 6 @@ -219,7 +219,7 @@ 2, 1 ], - "name": "assignment.js", + "filepath": "assignment.js", "end": [ 2, 6 @@ -236,9 +236,9 @@ "filePaths": [ "assignment.js" ], - "sha1": "53d0889371bf94bcfac80d7650321255b41eeb38", + "sha1": "f509f4afce54da5e15cbd2fe7db4d9f085618bdb", "gitDir": "test/corpus/repos/javascript", - "sha2": "f1f84edf5d0d233cb48a55774f0ee44cdb8143f6" + "sha2": "99d8addc7a4ef176a195a207bb8cf91d525f97d3" } ,{ "testCaseDescription": "javascript-assignment-delete-test", @@ -252,7 +252,7 @@ 1, 1 ], - "name": "assignment.js", + "filepath": "assignment.js", "end": [ 1, 6 @@ -269,9 +269,9 @@ "filePaths": [ "assignment.js" ], - "sha1": "f1f84edf5d0d233cb48a55774f0ee44cdb8143f6", + "sha1": "99d8addc7a4ef176a195a207bb8cf91d525f97d3", "gitDir": "test/corpus/repos/javascript", - "sha2": "358d66dc46c668b9e484e97231882e45e366d03f" + "sha2": "6cf0d4642ee45adf11ace0a165ccca1bf8f31afe" } ,{ "testCaseDescription": "javascript-assignment-delete-rest-test", @@ -285,7 +285,7 @@ 1, 1 ], - "name": "assignment.js", + "filepath": "assignment.js", "end": [ 1, 6 @@ -302,7 +302,7 @@ "filePaths": [ "assignment.js" ], - "sha1": "358d66dc46c668b9e484e97231882e45e366d03f", + "sha1": "6cf0d4642ee45adf11ace0a165ccca1bf8f31afe", "gitDir": "test/corpus/repos/javascript", - "sha2": "a4003ba4e78b0ae460decba084c34b15da1aa05e" + "sha2": "b2efc6921b13a351504269178cfdd7b8feb2cca1" }] diff --git a/test/corpus/diff-summaries/javascript/bitwise-operator.json b/test/corpus/diff-summaries/javascript/bitwise-operator.json index d9477385f..6e9f834d5 100644 --- a/test/corpus/diff-summaries/javascript/bitwise-operator.json +++ b/test/corpus/diff-summaries/javascript/bitwise-operator.json @@ -10,7 +10,7 @@ 1, 1 ], - "name": "bitwise-operator.js", + "filepath": "bitwise-operator.js", "end": [ 1, 7 @@ -27,9 +27,9 @@ "filePaths": [ "bitwise-operator.js" ], - "sha1": "8a735ff7a31a77424b93ff74548a5ca81e1dba3f", + "sha1": "1eec94ffb9b040257cafa5072d19b25f14a33263", "gitDir": "test/corpus/repos/javascript", - "sha2": "4e79490e2d815ab0f81dd5cec2022bf83f3ed235" + "sha2": "30f68d7dd11df4d82141aa25e30bf22e944b7e8c" } ,{ "testCaseDescription": "javascript-bitwise-operator-replacement-insert-test", @@ -43,7 +43,7 @@ 1, 1 ], - "name": "bitwise-operator.js", + "filepath": "bitwise-operator.js", "end": [ 1, 7 @@ -60,7 +60,7 @@ 2, 1 ], - "name": "bitwise-operator.js", + "filepath": "bitwise-operator.js", "end": [ 2, 7 @@ -77,9 +77,9 @@ "filePaths": [ "bitwise-operator.js" ], - "sha1": "4e79490e2d815ab0f81dd5cec2022bf83f3ed235", + "sha1": "30f68d7dd11df4d82141aa25e30bf22e944b7e8c", "gitDir": "test/corpus/repos/javascript", - "sha2": "72d4748300623514be5fd407a75cff6b3378b955" + "sha2": "8f3714e23c1c45e4ea0f0ca881ec61587847bc28" } ,{ "testCaseDescription": "javascript-bitwise-operator-delete-insert-test", @@ -94,7 +94,7 @@ 1, 6 ], - "name": "bitwise-operator.js", + "filepath": "bitwise-operator.js", "end": [ 1, 7 @@ -105,7 +105,7 @@ 1, 6 ], - "name": "bitwise-operator.js", + "filepath": "bitwise-operator.js", "end": [ 1, 7 @@ -123,9 +123,9 @@ "filePaths": [ "bitwise-operator.js" ], - "sha1": "72d4748300623514be5fd407a75cff6b3378b955", + "sha1": "8f3714e23c1c45e4ea0f0ca881ec61587847bc28", "gitDir": "test/corpus/repos/javascript", - "sha2": "69b73f68b68e2ab525a929d74e3a43df64ef88b4" + "sha2": "741a0c2e36a58dd74d2ebe88649be45b8599461e" } ,{ "testCaseDescription": "javascript-bitwise-operator-replacement-test", @@ -140,7 +140,7 @@ 1, 6 ], - "name": "bitwise-operator.js", + "filepath": "bitwise-operator.js", "end": [ 1, 7 @@ -151,7 +151,7 @@ 1, 6 ], - "name": "bitwise-operator.js", + "filepath": "bitwise-operator.js", "end": [ 1, 7 @@ -169,9 +169,9 @@ "filePaths": [ "bitwise-operator.js" ], - "sha1": "69b73f68b68e2ab525a929d74e3a43df64ef88b4", + "sha1": "741a0c2e36a58dd74d2ebe88649be45b8599461e", "gitDir": "test/corpus/repos/javascript", - "sha2": "c12333aa2b749340791848b0f57610a5c6b52faf" + "sha2": "e2fc526fde736efe55c5827a911a530485a15004" } ,{ "testCaseDescription": "javascript-bitwise-operator-delete-replacement-test", @@ -185,7 +185,7 @@ 1, 1 ], - "name": "bitwise-operator.js", + "filepath": "bitwise-operator.js", "end": [ 1, 7 @@ -202,7 +202,7 @@ 2, 1 ], - "name": "bitwise-operator.js", + "filepath": "bitwise-operator.js", "end": [ 2, 7 @@ -219,7 +219,7 @@ 2, 1 ], - "name": "bitwise-operator.js", + "filepath": "bitwise-operator.js", "end": [ 2, 7 @@ -236,9 +236,9 @@ "filePaths": [ "bitwise-operator.js" ], - "sha1": "c12333aa2b749340791848b0f57610a5c6b52faf", + "sha1": "e2fc526fde736efe55c5827a911a530485a15004", "gitDir": "test/corpus/repos/javascript", - "sha2": "1e669bdb2a1cd74b9f08dd9b1aa43014973a1f8c" + "sha2": "45721058bcdb26087b7c87c506315bb6e07007a8" } ,{ "testCaseDescription": "javascript-bitwise-operator-delete-test", @@ -252,7 +252,7 @@ 1, 1 ], - "name": "bitwise-operator.js", + "filepath": "bitwise-operator.js", "end": [ 1, 7 @@ -269,9 +269,9 @@ "filePaths": [ "bitwise-operator.js" ], - "sha1": "1e669bdb2a1cd74b9f08dd9b1aa43014973a1f8c", + "sha1": "45721058bcdb26087b7c87c506315bb6e07007a8", "gitDir": "test/corpus/repos/javascript", - "sha2": "ac8d1c7f04041084bdee5e5d66b09735976372c2" + "sha2": "fa89fd128d8f8480cfabfc30e39c1bab2ccd090e" } ,{ "testCaseDescription": "javascript-bitwise-operator-delete-rest-test", @@ -285,7 +285,7 @@ 1, 1 ], - "name": "bitwise-operator.js", + "filepath": "bitwise-operator.js", "end": [ 1, 7 @@ -302,7 +302,7 @@ "filePaths": [ "bitwise-operator.js" ], - "sha1": "ac8d1c7f04041084bdee5e5d66b09735976372c2", + "sha1": "fa89fd128d8f8480cfabfc30e39c1bab2ccd090e", "gitDir": "test/corpus/repos/javascript", - "sha2": "088c27d2d4e2150bac4bff85c129df8d90a407c2" + "sha2": "024f82fddfdef0b3d3e3778c756268054fa2918b" }] diff --git a/test/corpus/diff-summaries/javascript/boolean-operator.json b/test/corpus/diff-summaries/javascript/boolean-operator.json index bd975a9c8..20df4a9ca 100644 --- a/test/corpus/diff-summaries/javascript/boolean-operator.json +++ b/test/corpus/diff-summaries/javascript/boolean-operator.json @@ -10,7 +10,7 @@ 1, 1 ], - "name": "boolean-operator.js", + "filepath": "boolean-operator.js", "end": [ 1, 7 @@ -27,9 +27,9 @@ "filePaths": [ "boolean-operator.js" ], - "sha1": "4a00f98e1f34850ca8d14b8f33de4f8a0fcb7c40", + "sha1": "30525e7478269d5b5412bfef35746e7a3e3800f6", "gitDir": "test/corpus/repos/javascript", - "sha2": "95d128540dedb5ebcc33abd84e10116e0fd05c50" + "sha2": "57ebb0e5f08ff3b101191a8eb240204030942a34" } ,{ "testCaseDescription": "javascript-boolean-operator-replacement-insert-test", @@ -43,7 +43,7 @@ 1, 1 ], - "name": "boolean-operator.js", + "filepath": "boolean-operator.js", "end": [ 1, 7 @@ -60,7 +60,7 @@ 2, 1 ], - "name": "boolean-operator.js", + "filepath": "boolean-operator.js", "end": [ 2, 7 @@ -77,9 +77,9 @@ "filePaths": [ "boolean-operator.js" ], - "sha1": "95d128540dedb5ebcc33abd84e10116e0fd05c50", + "sha1": "57ebb0e5f08ff3b101191a8eb240204030942a34", "gitDir": "test/corpus/repos/javascript", - "sha2": "ae35cc9ea4ccbcaf06b7156b11ca36fb217b50da" + "sha2": "70ffeaeafa290d1a07f30c05a4f98c66ecfc27b3" } ,{ "testCaseDescription": "javascript-boolean-operator-delete-insert-test", @@ -90,9 +90,9 @@ "filePaths": [ "boolean-operator.js" ], - "sha1": "ae35cc9ea4ccbcaf06b7156b11ca36fb217b50da", + "sha1": "70ffeaeafa290d1a07f30c05a4f98c66ecfc27b3", "gitDir": "test/corpus/repos/javascript", - "sha2": "44bf52b057f77b274462a57449b1a91efaa6b206" + "sha2": "f6c30aabfcb6c3edd072326c703ccfdeafe48d4b" } ,{ "testCaseDescription": "javascript-boolean-operator-replacement-test", @@ -103,9 +103,9 @@ "filePaths": [ "boolean-operator.js" ], - "sha1": "44bf52b057f77b274462a57449b1a91efaa6b206", + "sha1": "f6c30aabfcb6c3edd072326c703ccfdeafe48d4b", "gitDir": "test/corpus/repos/javascript", - "sha2": "045f496374fb481d0b8ffdd5792f8ee519eb8389" + "sha2": "9c8103da0a53aa68386529151d94bc3e877733f0" } ,{ "testCaseDescription": "javascript-boolean-operator-delete-replacement-test", @@ -119,7 +119,7 @@ 1, 1 ], - "name": "boolean-operator.js", + "filepath": "boolean-operator.js", "end": [ 1, 7 @@ -136,9 +136,9 @@ "filePaths": [ "boolean-operator.js" ], - "sha1": "045f496374fb481d0b8ffdd5792f8ee519eb8389", + "sha1": "9c8103da0a53aa68386529151d94bc3e877733f0", "gitDir": "test/corpus/repos/javascript", - "sha2": "abe63da8bfcb6f56c48ae2cefc32dffb8707b534" + "sha2": "339aacd26dddf1450078fc68a13384757c9da3af" } ,{ "testCaseDescription": "javascript-boolean-operator-delete-test", @@ -152,7 +152,7 @@ 1, 1 ], - "name": "boolean-operator.js", + "filepath": "boolean-operator.js", "end": [ 1, 7 @@ -169,9 +169,9 @@ "filePaths": [ "boolean-operator.js" ], - "sha1": "abe63da8bfcb6f56c48ae2cefc32dffb8707b534", + "sha1": "339aacd26dddf1450078fc68a13384757c9da3af", "gitDir": "test/corpus/repos/javascript", - "sha2": "30cb690c861b4c9f1c92857e4098043dd7165fa1" + "sha2": "56b907aabebbd480b6e795ef64c688f5debf68f6" } ,{ "testCaseDescription": "javascript-boolean-operator-delete-rest-test", @@ -185,7 +185,7 @@ 1, 1 ], - "name": "boolean-operator.js", + "filepath": "boolean-operator.js", "end": [ 1, 7 @@ -202,7 +202,7 @@ "filePaths": [ "boolean-operator.js" ], - "sha1": "30cb690c861b4c9f1c92857e4098043dd7165fa1", + "sha1": "56b907aabebbd480b6e795ef64c688f5debf68f6", "gitDir": "test/corpus/repos/javascript", - "sha2": "8a735ff7a31a77424b93ff74548a5ca81e1dba3f" + "sha2": "9fa09a55dece8769da1ceb27c7799cf9ad731cd7" }] diff --git a/test/corpus/diff-summaries/javascript/chained-callbacks.json b/test/corpus/diff-summaries/javascript/chained-callbacks.json index eb5f48219..eed6342a0 100644 --- a/test/corpus/diff-summaries/javascript/chained-callbacks.json +++ b/test/corpus/diff-summaries/javascript/chained-callbacks.json @@ -10,7 +10,7 @@ 1, 1 ], - "name": "chained-callbacks.js", + "filepath": "chained-callbacks.js", "end": [ 1, 39 @@ -27,9 +27,9 @@ "filePaths": [ "chained-callbacks.js" ], - "sha1": "20bc26cc8af9efd835b023b026250f920bf1cc88", + "sha1": "3c18b9342d8e60bf5c240ca798986c380dcf3110", "gitDir": "test/corpus/repos/javascript", - "sha2": "8c05a8c012b065745a2da67a5a6e1bce328fd6b6" + "sha2": "ef9e7888e6ba75fa08ff3a4884ec12b07aeac1d0" } ,{ "testCaseDescription": "javascript-chained-callbacks-replacement-insert-test", @@ -43,7 +43,7 @@ 1, 1 ], - "name": "chained-callbacks.js", + "filepath": "chained-callbacks.js", "end": [ 1, 42 @@ -60,7 +60,7 @@ 2, 1 ], - "name": "chained-callbacks.js", + "filepath": "chained-callbacks.js", "end": [ 2, 39 @@ -77,9 +77,9 @@ "filePaths": [ "chained-callbacks.js" ], - "sha1": "8c05a8c012b065745a2da67a5a6e1bce328fd6b6", + "sha1": "ef9e7888e6ba75fa08ff3a4884ec12b07aeac1d0", "gitDir": "test/corpus/repos/javascript", - "sha2": "6869215944dfc529db1c0e731d0640f9a85d1040" + "sha2": "5fe5195d5f0b8416e5863a91cc91675c1a043c76" } ,{ "testCaseDescription": "javascript-chained-callbacks-delete-insert-test", @@ -94,7 +94,7 @@ 1, 6 ], - "name": "chained-callbacks.js", + "filepath": "chained-callbacks.js", "end": [ 1, 12 @@ -105,7 +105,7 @@ 1, 6 ], - "name": "chained-callbacks.js", + "filepath": "chained-callbacks.js", "end": [ 1, 9 @@ -124,7 +124,7 @@ 1, 35 ], - "name": "chained-callbacks.js", + "filepath": "chained-callbacks.js", "end": [ 1, 36 @@ -135,7 +135,7 @@ 1, 32 ], - "name": "chained-callbacks.js", + "filepath": "chained-callbacks.js", "end": [ 1, 33 @@ -154,7 +154,7 @@ 1, 37 ], - "name": "chained-callbacks.js", + "filepath": "chained-callbacks.js", "end": [ 1, 38 @@ -165,7 +165,7 @@ 1, 34 ], - "name": "chained-callbacks.js", + "filepath": "chained-callbacks.js", "end": [ 1, 35 @@ -183,9 +183,9 @@ "filePaths": [ "chained-callbacks.js" ], - "sha1": "6869215944dfc529db1c0e731d0640f9a85d1040", + "sha1": "5fe5195d5f0b8416e5863a91cc91675c1a043c76", "gitDir": "test/corpus/repos/javascript", - "sha2": "4c964599e2c3f646a49bd3c5a0ad7f28bb4e76f8" + "sha2": "e1ad8c6994e5e3e475b0450190c14a830621f2e8" } ,{ "testCaseDescription": "javascript-chained-callbacks-replacement-test", @@ -200,7 +200,7 @@ 1, 6 ], - "name": "chained-callbacks.js", + "filepath": "chained-callbacks.js", "end": [ 1, 9 @@ -211,7 +211,7 @@ 1, 6 ], - "name": "chained-callbacks.js", + "filepath": "chained-callbacks.js", "end": [ 1, 12 @@ -230,7 +230,7 @@ 1, 32 ], - "name": "chained-callbacks.js", + "filepath": "chained-callbacks.js", "end": [ 1, 33 @@ -241,7 +241,7 @@ 1, 35 ], - "name": "chained-callbacks.js", + "filepath": "chained-callbacks.js", "end": [ 1, 36 @@ -260,7 +260,7 @@ 1, 34 ], - "name": "chained-callbacks.js", + "filepath": "chained-callbacks.js", "end": [ 1, 35 @@ -271,7 +271,7 @@ 1, 37 ], - "name": "chained-callbacks.js", + "filepath": "chained-callbacks.js", "end": [ 1, 38 @@ -289,9 +289,9 @@ "filePaths": [ "chained-callbacks.js" ], - "sha1": "4c964599e2c3f646a49bd3c5a0ad7f28bb4e76f8", + "sha1": "e1ad8c6994e5e3e475b0450190c14a830621f2e8", "gitDir": "test/corpus/repos/javascript", - "sha2": "20c8a9a737d91e365f686ac9ef3ea3ece6bcf5ed" + "sha2": "be21199a2c109eaf01d8964f7dceb5242bd94c5c" } ,{ "testCaseDescription": "javascript-chained-callbacks-delete-replacement-test", @@ -305,7 +305,7 @@ 1, 1 ], - "name": "chained-callbacks.js", + "filepath": "chained-callbacks.js", "end": [ 1, 42 @@ -322,7 +322,7 @@ 2, 1 ], - "name": "chained-callbacks.js", + "filepath": "chained-callbacks.js", "end": [ 2, 39 @@ -339,7 +339,7 @@ 2, 1 ], - "name": "chained-callbacks.js", + "filepath": "chained-callbacks.js", "end": [ 2, 42 @@ -356,9 +356,9 @@ "filePaths": [ "chained-callbacks.js" ], - "sha1": "20c8a9a737d91e365f686ac9ef3ea3ece6bcf5ed", + "sha1": "be21199a2c109eaf01d8964f7dceb5242bd94c5c", "gitDir": "test/corpus/repos/javascript", - "sha2": "883ffc29d09b541a5c4d9e4674d5c04f876a40a2" + "sha2": "a0cca877bad5d1aa7a3e0ebf9d9c04cf828e4176" } ,{ "testCaseDescription": "javascript-chained-callbacks-delete-test", @@ -372,7 +372,7 @@ 1, 1 ], - "name": "chained-callbacks.js", + "filepath": "chained-callbacks.js", "end": [ 1, 39 @@ -389,9 +389,9 @@ "filePaths": [ "chained-callbacks.js" ], - "sha1": "883ffc29d09b541a5c4d9e4674d5c04f876a40a2", + "sha1": "a0cca877bad5d1aa7a3e0ebf9d9c04cf828e4176", "gitDir": "test/corpus/repos/javascript", - "sha2": "76d7d961c5ea2ade3fdd136a056c683732a81a25" + "sha2": "052b9850290f471a3fefc219133f72d90ddf7c9d" } ,{ "testCaseDescription": "javascript-chained-callbacks-delete-rest-test", @@ -405,7 +405,7 @@ 1, 1 ], - "name": "chained-callbacks.js", + "filepath": "chained-callbacks.js", "end": [ 1, 42 @@ -422,7 +422,7 @@ "filePaths": [ "chained-callbacks.js" ], - "sha1": "76d7d961c5ea2ade3fdd136a056c683732a81a25", + "sha1": "052b9850290f471a3fefc219133f72d90ddf7c9d", "gitDir": "test/corpus/repos/javascript", - "sha2": "bd29fccbe38961789cd724a6537993e68f491091" + "sha2": "3c341577267bfb8873272dbf6be1d4727516b67a" }] diff --git a/test/corpus/diff-summaries/javascript/chained-property-access.json b/test/corpus/diff-summaries/javascript/chained-property-access.json index 3ba8b8003..8e6140515 100644 --- a/test/corpus/diff-summaries/javascript/chained-property-access.json +++ b/test/corpus/diff-summaries/javascript/chained-property-access.json @@ -10,7 +10,7 @@ 1, 1 ], - "name": "chained-property-access.js", + "filepath": "chained-property-access.js", "end": [ 2, 1 @@ -27,9 +27,9 @@ "filePaths": [ "chained-property-access.js" ], - "sha1": "9dc1c8722d84e3f245688e90b8cf7155c95f446f", + "sha1": "235008297e273479683591ad4b1f46b69655f0e8", "gitDir": "test/corpus/repos/javascript", - "sha2": "8afef92d997e837342429dbbacb19365f39eb7b4" + "sha2": "b0e7d678e5314b2147723f6147dc047f5443a230" } ,{ "testCaseDescription": "javascript-chained-property-access-replacement-insert-test", @@ -43,7 +43,7 @@ 1, 1 ], - "name": "chained-property-access.js", + "filepath": "chained-property-access.js", "end": [ 2, 1 @@ -60,7 +60,7 @@ 2, 1 ], - "name": "chained-property-access.js", + "filepath": "chained-property-access.js", "end": [ 3, 1 @@ -77,9 +77,9 @@ "filePaths": [ "chained-property-access.js" ], - "sha1": "8afef92d997e837342429dbbacb19365f39eb7b4", + "sha1": "b0e7d678e5314b2147723f6147dc047f5443a230", "gitDir": "test/corpus/repos/javascript", - "sha2": "4475e0d7eb0e590853f495dd1db81601b6bc9dd3" + "sha2": "a1a002230ad2e478d4aa03a58947035fa3be411f" } ,{ "testCaseDescription": "javascript-chained-property-access-delete-insert-test", @@ -94,7 +94,7 @@ 1, 33 ], - "name": "chained-property-access.js", + "filepath": "chained-property-access.js", "end": [ 1, 43 @@ -105,7 +105,7 @@ 1, 33 ], - "name": "chained-property-access.js", + "filepath": "chained-property-access.js", "end": [ 1, 41 @@ -124,7 +124,7 @@ 1, 60 ], - "name": "chained-property-access.js", + "filepath": "chained-property-access.js", "end": [ 1, 70 @@ -135,7 +135,7 @@ 1, 58 ], - "name": "chained-property-access.js", + "filepath": "chained-property-access.js", "end": [ 1, 66 @@ -153,9 +153,9 @@ "filePaths": [ "chained-property-access.js" ], - "sha1": "4475e0d7eb0e590853f495dd1db81601b6bc9dd3", + "sha1": "a1a002230ad2e478d4aa03a58947035fa3be411f", "gitDir": "test/corpus/repos/javascript", - "sha2": "030352703839b25bbdacac36ddeabb1a831ad05a" + "sha2": "86087e1f8e29b4e961baa7debe02cdc1fc1befb1" } ,{ "testCaseDescription": "javascript-chained-property-access-replacement-test", @@ -170,7 +170,7 @@ 1, 33 ], - "name": "chained-property-access.js", + "filepath": "chained-property-access.js", "end": [ 1, 41 @@ -181,7 +181,7 @@ 1, 33 ], - "name": "chained-property-access.js", + "filepath": "chained-property-access.js", "end": [ 1, 43 @@ -200,7 +200,7 @@ 1, 58 ], - "name": "chained-property-access.js", + "filepath": "chained-property-access.js", "end": [ 1, 66 @@ -211,7 +211,7 @@ 1, 60 ], - "name": "chained-property-access.js", + "filepath": "chained-property-access.js", "end": [ 1, 70 @@ -229,9 +229,9 @@ "filePaths": [ "chained-property-access.js" ], - "sha1": "030352703839b25bbdacac36ddeabb1a831ad05a", + "sha1": "86087e1f8e29b4e961baa7debe02cdc1fc1befb1", "gitDir": "test/corpus/repos/javascript", - "sha2": "59dd2644428d0c34aa9181e402e1bb4e823ea8de" + "sha2": "611cf1de89471aa50d852eb2da70f9d657c286e1" } ,{ "testCaseDescription": "javascript-chained-property-access-delete-replacement-test", @@ -245,7 +245,7 @@ 1, 1 ], - "name": "chained-property-access.js", + "filepath": "chained-property-access.js", "end": [ 2, 1 @@ -262,7 +262,7 @@ 2, 1 ], - "name": "chained-property-access.js", + "filepath": "chained-property-access.js", "end": [ 3, 1 @@ -279,7 +279,7 @@ 2, 1 ], - "name": "chained-property-access.js", + "filepath": "chained-property-access.js", "end": [ 3, 1 @@ -296,9 +296,9 @@ "filePaths": [ "chained-property-access.js" ], - "sha1": "59dd2644428d0c34aa9181e402e1bb4e823ea8de", + "sha1": "611cf1de89471aa50d852eb2da70f9d657c286e1", "gitDir": "test/corpus/repos/javascript", - "sha2": "bad1b125972f03fd282dbf26f9adfa1315031ca7" + "sha2": "ee3cfec8a54e6491d694db9019b1adcd976bb6ba" } ,{ "testCaseDescription": "javascript-chained-property-access-delete-test", @@ -312,7 +312,7 @@ 1, 1 ], - "name": "chained-property-access.js", + "filepath": "chained-property-access.js", "end": [ 2, 1 @@ -329,9 +329,9 @@ "filePaths": [ "chained-property-access.js" ], - "sha1": "bad1b125972f03fd282dbf26f9adfa1315031ca7", + "sha1": "ee3cfec8a54e6491d694db9019b1adcd976bb6ba", "gitDir": "test/corpus/repos/javascript", - "sha2": "cf0b7cc3662ba96a6efe6d01c4baf13e04e1a789" + "sha2": "341ec07cbdf4549bbe01e28bd6f21ff53fe1495c" } ,{ "testCaseDescription": "javascript-chained-property-access-delete-rest-test", @@ -345,7 +345,7 @@ 1, 1 ], - "name": "chained-property-access.js", + "filepath": "chained-property-access.js", "end": [ 2, 1 @@ -362,7 +362,7 @@ "filePaths": [ "chained-property-access.js" ], - "sha1": "cf0b7cc3662ba96a6efe6d01c4baf13e04e1a789", + "sha1": "341ec07cbdf4549bbe01e28bd6f21ff53fe1495c", "gitDir": "test/corpus/repos/javascript", - "sha2": "20bc26cc8af9efd835b023b026250f920bf1cc88" + "sha2": "dbe7e1fb21efaf093196c76c7153bb2fbc3b7143" }] diff --git a/test/corpus/diff-summaries/javascript/class.json b/test/corpus/diff-summaries/javascript/class.json index 5df1a0a05..0743e5b32 100644 --- a/test/corpus/diff-summaries/javascript/class.json +++ b/test/corpus/diff-summaries/javascript/class.json @@ -10,7 +10,7 @@ 1, 1 ], - "name": "class.js", + "filepath": "class.js", "end": [ 1, 87 @@ -27,9 +27,9 @@ "filePaths": [ "class.js" ], - "sha1": "a73251e778f05b8cbe501d5f6ea0c483640ced20", + "sha1": "a77ec4befeb4574a4433a062878d43b231a916bc", "gitDir": "test/corpus/repos/javascript", - "sha2": "d14f6c7cb29e72223e5d2c7170379f99f8a893b2" + "sha2": "41dc947bf0ee187b5783d62de471d6c74cdf6df2" } ,{ "testCaseDescription": "javascript-class-replacement-insert-test", @@ -43,7 +43,7 @@ 1, 1 ], - "name": "class.js", + "filepath": "class.js", "end": [ 1, 85 @@ -60,7 +60,7 @@ 2, 1 ], - "name": "class.js", + "filepath": "class.js", "end": [ 2, 87 @@ -77,9 +77,9 @@ "filePaths": [ "class.js" ], - "sha1": "d14f6c7cb29e72223e5d2c7170379f99f8a893b2", + "sha1": "41dc947bf0ee187b5783d62de471d6c74cdf6df2", "gitDir": "test/corpus/repos/javascript", - "sha2": "7c73aea04cb45042bf232a448d426be9ae888a9b" + "sha2": "ad979810f114bac8db323d00a003eff85983f777" } ,{ "testCaseDescription": "javascript-class-delete-insert-test", @@ -94,7 +94,7 @@ 1, 20 ], - "name": "class.js", + "filepath": "class.js", "end": [ 1, 23 @@ -105,7 +105,7 @@ 1, 20 ], - "name": "class.js", + "filepath": "class.js", "end": [ 1, 23 @@ -124,7 +124,7 @@ 1, 42 ], - "name": "class.js", + "filepath": "class.js", "end": [ 1, 45 @@ -135,7 +135,7 @@ 1, 42 ], - "name": "class.js", + "filepath": "class.js", "end": [ 1, 45 @@ -154,7 +154,7 @@ 1, 63 ], - "name": "class.js", + "filepath": "class.js", "end": [ 1, 66 @@ -165,7 +165,7 @@ 1, 63 ], - "name": "class.js", + "filepath": "class.js", "end": [ 1, 68 @@ -183,9 +183,9 @@ "filePaths": [ "class.js" ], - "sha1": "7c73aea04cb45042bf232a448d426be9ae888a9b", + "sha1": "ad979810f114bac8db323d00a003eff85983f777", "gitDir": "test/corpus/repos/javascript", - "sha2": "aecfbbcd53407a567f46a40cad9270e0bf22458a" + "sha2": "fcb3d418dbb3440d98664e22a3ce8ed40ccfb8a6" } ,{ "testCaseDescription": "javascript-class-replacement-test", @@ -200,7 +200,7 @@ 1, 20 ], - "name": "class.js", + "filepath": "class.js", "end": [ 1, 23 @@ -211,7 +211,7 @@ 1, 20 ], - "name": "class.js", + "filepath": "class.js", "end": [ 1, 23 @@ -230,7 +230,7 @@ 1, 42 ], - "name": "class.js", + "filepath": "class.js", "end": [ 1, 45 @@ -241,7 +241,7 @@ 1, 42 ], - "name": "class.js", + "filepath": "class.js", "end": [ 1, 45 @@ -260,7 +260,7 @@ 1, 63 ], - "name": "class.js", + "filepath": "class.js", "end": [ 1, 68 @@ -271,7 +271,7 @@ 1, 63 ], - "name": "class.js", + "filepath": "class.js", "end": [ 1, 66 @@ -289,9 +289,9 @@ "filePaths": [ "class.js" ], - "sha1": "aecfbbcd53407a567f46a40cad9270e0bf22458a", + "sha1": "fcb3d418dbb3440d98664e22a3ce8ed40ccfb8a6", "gitDir": "test/corpus/repos/javascript", - "sha2": "f35ad41e7a506af4049a99149a8f42fe403fd3c2" + "sha2": "bb881c2e2459f032b76724998560c185e8282c51" } ,{ "testCaseDescription": "javascript-class-delete-replacement-test", @@ -305,7 +305,7 @@ 1, 1 ], - "name": "class.js", + "filepath": "class.js", "end": [ 1, 85 @@ -322,7 +322,7 @@ 2, 1 ], - "name": "class.js", + "filepath": "class.js", "end": [ 2, 87 @@ -339,7 +339,7 @@ 2, 1 ], - "name": "class.js", + "filepath": "class.js", "end": [ 2, 85 @@ -356,9 +356,9 @@ "filePaths": [ "class.js" ], - "sha1": "f35ad41e7a506af4049a99149a8f42fe403fd3c2", + "sha1": "bb881c2e2459f032b76724998560c185e8282c51", "gitDir": "test/corpus/repos/javascript", - "sha2": "408c1f0028eff597ce2334d8b98a0692fbc32ee2" + "sha2": "6b97add2716043508dd60d4ab6d35399d708a603" } ,{ "testCaseDescription": "javascript-class-delete-test", @@ -372,7 +372,7 @@ 1, 1 ], - "name": "class.js", + "filepath": "class.js", "end": [ 1, 87 @@ -389,9 +389,9 @@ "filePaths": [ "class.js" ], - "sha1": "408c1f0028eff597ce2334d8b98a0692fbc32ee2", + "sha1": "6b97add2716043508dd60d4ab6d35399d708a603", "gitDir": "test/corpus/repos/javascript", - "sha2": "1414ce434ca9fe4f8b0cdfb16e7e50bcdd12055f" + "sha2": "1508d11e42bb6de8bdabee2f19e7f90bf2b8925c" } ,{ "testCaseDescription": "javascript-class-delete-rest-test", @@ -405,7 +405,7 @@ 1, 1 ], - "name": "class.js", + "filepath": "class.js", "end": [ 1, 85 @@ -422,7 +422,7 @@ "filePaths": [ "class.js" ], - "sha1": "1414ce434ca9fe4f8b0cdfb16e7e50bcdd12055f", + "sha1": "1508d11e42bb6de8bdabee2f19e7f90bf2b8925c", "gitDir": "test/corpus/repos/javascript", - "sha2": "04b681e1190310f6148595f3d80260ae13299d43" + "sha2": "a6be8db7f10bd0797e3bcfbbfa28b19f82697dfe" }] diff --git a/test/corpus/diff-summaries/javascript/comma-operator.json b/test/corpus/diff-summaries/javascript/comma-operator.json index dfba42dc6..ce0edf185 100644 --- a/test/corpus/diff-summaries/javascript/comma-operator.json +++ b/test/corpus/diff-summaries/javascript/comma-operator.json @@ -10,7 +10,7 @@ 1, 1 ], - "name": "comma-operator.js", + "filepath": "comma-operator.js", "end": [ 1, 6 @@ -27,7 +27,7 @@ 1, 8 ], - "name": "comma-operator.js", + "filepath": "comma-operator.js", "end": [ 1, 13 @@ -44,9 +44,9 @@ "filePaths": [ "comma-operator.js" ], - "sha1": "462756b98c54f0b7551f56ee43c309cf51fd64a2", + "sha1": "5b0cc45ea8aec7a1271b0a8f6c69a5ec394d3466", "gitDir": "test/corpus/repos/javascript", - "sha2": "9302084f6e6aa45c6f4f21f362c0fdc2f5ee9789" + "sha2": "55cec91b966d01528f774b809cb653c4fc90efff" } ,{ "testCaseDescription": "javascript-comma-operator-replacement-insert-test", @@ -60,7 +60,7 @@ 1, 1 ], - "name": "comma-operator.js", + "filepath": "comma-operator.js", "end": [ 1, 23 @@ -77,7 +77,7 @@ 2, 1 ], - "name": "comma-operator.js", + "filepath": "comma-operator.js", "end": [ 2, 6 @@ -94,7 +94,7 @@ 2, 8 ], - "name": "comma-operator.js", + "filepath": "comma-operator.js", "end": [ 2, 13 @@ -111,9 +111,9 @@ "filePaths": [ "comma-operator.js" ], - "sha1": "9302084f6e6aa45c6f4f21f362c0fdc2f5ee9789", + "sha1": "55cec91b966d01528f774b809cb653c4fc90efff", "gitDir": "test/corpus/repos/javascript", - "sha2": "664fefa1822fe80ff2b7f48c3bdaf380b8efce49" + "sha2": "5fc2fe77223cee81fb9d7bc47e8d6fb7913b7e6b" } ,{ "testCaseDescription": "javascript-comma-operator-delete-insert-test", @@ -127,7 +127,7 @@ 1, 1 ], - "name": "comma-operator.js", + "filepath": "comma-operator.js", "end": [ 1, 6 @@ -144,7 +144,7 @@ 1, 8 ], - "name": "comma-operator.js", + "filepath": "comma-operator.js", "end": [ 1, 13 @@ -161,7 +161,7 @@ 1, 1 ], - "name": "comma-operator.js", + "filepath": "comma-operator.js", "end": [ 1, 23 @@ -178,9 +178,9 @@ "filePaths": [ "comma-operator.js" ], - "sha1": "664fefa1822fe80ff2b7f48c3bdaf380b8efce49", + "sha1": "5fc2fe77223cee81fb9d7bc47e8d6fb7913b7e6b", "gitDir": "test/corpus/repos/javascript", - "sha2": "209e54cd2325e3b40e4fb2429bbdd353cb11df96" + "sha2": "6dce0b8c842c231f2687b8c241c216182f904c52" } ,{ "testCaseDescription": "javascript-comma-operator-replacement-test", @@ -194,7 +194,7 @@ 1, 1 ], - "name": "comma-operator.js", + "filepath": "comma-operator.js", "end": [ 1, 23 @@ -211,7 +211,7 @@ 1, 1 ], - "name": "comma-operator.js", + "filepath": "comma-operator.js", "end": [ 1, 6 @@ -228,7 +228,7 @@ 1, 8 ], - "name": "comma-operator.js", + "filepath": "comma-operator.js", "end": [ 1, 13 @@ -245,9 +245,9 @@ "filePaths": [ "comma-operator.js" ], - "sha1": "209e54cd2325e3b40e4fb2429bbdd353cb11df96", + "sha1": "6dce0b8c842c231f2687b8c241c216182f904c52", "gitDir": "test/corpus/repos/javascript", - "sha2": "a396a8a09fff584b6cd8c3053f9bceee805e6ac3" + "sha2": "8f33ff537375c36fa25198b52496c983a63c8c71" } ,{ "testCaseDescription": "javascript-comma-operator-delete-replacement-test", @@ -261,7 +261,7 @@ 1, 1 ], - "name": "comma-operator.js", + "filepath": "comma-operator.js", "end": [ 1, 23 @@ -278,7 +278,7 @@ 2, 1 ], - "name": "comma-operator.js", + "filepath": "comma-operator.js", "end": [ 2, 6 @@ -295,7 +295,7 @@ 2, 8 ], - "name": "comma-operator.js", + "filepath": "comma-operator.js", "end": [ 2, 13 @@ -312,7 +312,7 @@ 2, 1 ], - "name": "comma-operator.js", + "filepath": "comma-operator.js", "end": [ 2, 23 @@ -329,9 +329,9 @@ "filePaths": [ "comma-operator.js" ], - "sha1": "a396a8a09fff584b6cd8c3053f9bceee805e6ac3", + "sha1": "8f33ff537375c36fa25198b52496c983a63c8c71", "gitDir": "test/corpus/repos/javascript", - "sha2": "438aa8fe676d5ddfeff0b8826369de84c9dc8c92" + "sha2": "b03508a044775fed4a0f71464e6c089e873b357e" } ,{ "testCaseDescription": "javascript-comma-operator-delete-test", @@ -345,7 +345,7 @@ 1, 1 ], - "name": "comma-operator.js", + "filepath": "comma-operator.js", "end": [ 1, 6 @@ -362,7 +362,7 @@ 1, 8 ], - "name": "comma-operator.js", + "filepath": "comma-operator.js", "end": [ 1, 13 @@ -379,9 +379,9 @@ "filePaths": [ "comma-operator.js" ], - "sha1": "438aa8fe676d5ddfeff0b8826369de84c9dc8c92", + "sha1": "b03508a044775fed4a0f71464e6c089e873b357e", "gitDir": "test/corpus/repos/javascript", - "sha2": "81c1a2f1b83654c6fadb49a595a94dbddde129ab" + "sha2": "7436dd0c850dea2efe5f09a9d83321d2011ead2f" } ,{ "testCaseDescription": "javascript-comma-operator-delete-rest-test", @@ -395,7 +395,7 @@ 1, 1 ], - "name": "comma-operator.js", + "filepath": "comma-operator.js", "end": [ 1, 23 @@ -412,7 +412,7 @@ "filePaths": [ "comma-operator.js" ], - "sha1": "81c1a2f1b83654c6fadb49a595a94dbddde129ab", + "sha1": "7436dd0c850dea2efe5f09a9d83321d2011ead2f", "gitDir": "test/corpus/repos/javascript", - "sha2": "e9872de5faf687bc02c8b7a06031ef152b2d3dbe" + "sha2": "8819ad193c4a1bcc9b075b3d3a4ae95e285b825c" }] diff --git a/test/corpus/diff-summaries/javascript/comment.json b/test/corpus/diff-summaries/javascript/comment.json index 6c8a07265..0a962ca4e 100644 --- a/test/corpus/diff-summaries/javascript/comment.json +++ b/test/corpus/diff-summaries/javascript/comment.json @@ -10,7 +10,7 @@ 1, 1 ], - "name": "comment.js", + "filepath": "comment.js", "end": [ 1, 22 @@ -27,9 +27,9 @@ "filePaths": [ "comment.js" ], - "sha1": "61540dc73cfaad0786519aca74727ab895384c00", + "sha1": "c23550df20b318fe7b1cb7a2656d09c75b7e364c", "gitDir": "test/corpus/repos/javascript", - "sha2": "93f50d2243f8c7646daf8fddb830df53de42d8f5" + "sha2": "4d8026fadbde01a719e79165a9d7b135b895f734" } ,{ "testCaseDescription": "javascript-comment-replacement-insert-test", @@ -43,7 +43,7 @@ 1, 1 ], - "name": "comment.js", + "filepath": "comment.js", "end": [ 3, 3 @@ -60,7 +60,7 @@ 4, 1 ], - "name": "comment.js", + "filepath": "comment.js", "end": [ 4, 22 @@ -77,9 +77,9 @@ "filePaths": [ "comment.js" ], - "sha1": "93f50d2243f8c7646daf8fddb830df53de42d8f5", + "sha1": "4d8026fadbde01a719e79165a9d7b135b895f734", "gitDir": "test/corpus/repos/javascript", - "sha2": "3ee6b1b429b8805f1051cbc143cc64d9462ba4d5" + "sha2": "1129255730208987db2c51558167275a5b3d4289" } ,{ "testCaseDescription": "javascript-comment-delete-insert-test", @@ -94,7 +94,7 @@ 1, 1 ], - "name": "comment.js", + "filepath": "comment.js", "end": [ 3, 3 @@ -105,7 +105,7 @@ 1, 1 ], - "name": "comment.js", + "filepath": "comment.js", "end": [ 1, 22 @@ -123,9 +123,9 @@ "filePaths": [ "comment.js" ], - "sha1": "3ee6b1b429b8805f1051cbc143cc64d9462ba4d5", + "sha1": "1129255730208987db2c51558167275a5b3d4289", "gitDir": "test/corpus/repos/javascript", - "sha2": "8873c3149ab63a064d4b6e59d9bab7b7e2c1da68" + "sha2": "1742cb324e484c556c1b9647512fac4ea4bfc712" } ,{ "testCaseDescription": "javascript-comment-replacement-test", @@ -140,7 +140,7 @@ 1, 1 ], - "name": "comment.js", + "filepath": "comment.js", "end": [ 1, 22 @@ -151,7 +151,7 @@ 1, 1 ], - "name": "comment.js", + "filepath": "comment.js", "end": [ 3, 3 @@ -169,9 +169,9 @@ "filePaths": [ "comment.js" ], - "sha1": "8873c3149ab63a064d4b6e59d9bab7b7e2c1da68", + "sha1": "1742cb324e484c556c1b9647512fac4ea4bfc712", "gitDir": "test/corpus/repos/javascript", - "sha2": "ce476dad66521fd00c2643b33d27d97f0ea06dc5" + "sha2": "bb3f52b636c10b6316d9aeef1beb0317aaf14059" } ,{ "testCaseDescription": "javascript-comment-delete-replacement-test", @@ -185,7 +185,7 @@ 1, 1 ], - "name": "comment.js", + "filepath": "comment.js", "end": [ 3, 3 @@ -202,7 +202,7 @@ 4, 1 ], - "name": "comment.js", + "filepath": "comment.js", "end": [ 4, 22 @@ -219,7 +219,7 @@ 2, 1 ], - "name": "comment.js", + "filepath": "comment.js", "end": [ 4, 3 @@ -236,9 +236,9 @@ "filePaths": [ "comment.js" ], - "sha1": "ce476dad66521fd00c2643b33d27d97f0ea06dc5", + "sha1": "bb3f52b636c10b6316d9aeef1beb0317aaf14059", "gitDir": "test/corpus/repos/javascript", - "sha2": "fae5624ac16f834275314d94ff7584a48542f0b5" + "sha2": "3354dca1f0212e3f3abf6a7c243ce6023f5e1d63" } ,{ "testCaseDescription": "javascript-comment-delete-test", @@ -252,7 +252,7 @@ 1, 1 ], - "name": "comment.js", + "filepath": "comment.js", "end": [ 1, 22 @@ -269,9 +269,9 @@ "filePaths": [ "comment.js" ], - "sha1": "fae5624ac16f834275314d94ff7584a48542f0b5", + "sha1": "3354dca1f0212e3f3abf6a7c243ce6023f5e1d63", "gitDir": "test/corpus/repos/javascript", - "sha2": "bfcfebda701bcee0da94c64a24d5ca11a03270df" + "sha2": "8bb17eddf8e2753e4b493120dbed5797d7ff0b3e" } ,{ "testCaseDescription": "javascript-comment-delete-rest-test", @@ -285,7 +285,7 @@ 1, 1 ], - "name": "comment.js", + "filepath": "comment.js", "end": [ 3, 3 @@ -302,7 +302,7 @@ "filePaths": [ "comment.js" ], - "sha1": "bfcfebda701bcee0da94c64a24d5ca11a03270df", + "sha1": "8bb17eddf8e2753e4b493120dbed5797d7ff0b3e", "gitDir": "test/corpus/repos/javascript", - "sha2": "7d081d5591b64adba332f89a0a3aeba494aa1b0e" + "sha2": "c557f1866ae568572f87ded09aa73ee1a303d97a" }] diff --git a/test/corpus/diff-summaries/javascript/constructor-call.json b/test/corpus/diff-summaries/javascript/constructor-call.json index 74791a7ea..928232bf1 100644 --- a/test/corpus/diff-summaries/javascript/constructor-call.json +++ b/test/corpus/diff-summaries/javascript/constructor-call.json @@ -10,7 +10,7 @@ 1, 1 ], - "name": "constructor-call.js", + "filepath": "constructor-call.js", "end": [ 1, 27 @@ -27,9 +27,9 @@ "filePaths": [ "constructor-call.js" ], - "sha1": "f110a993d59a58f31e4b09bd46734026c4fdcc60", + "sha1": "d045a78616b98743348a591843bc79453d97fbde", "gitDir": "test/corpus/repos/javascript", - "sha2": "c84bb50f8570d3b7620847bb6e53e5164da5dc97" + "sha2": "ab9ab388d28ec6986921e04ab6efb34e293a00f3" } ,{ "testCaseDescription": "javascript-constructor-call-replacement-insert-test", @@ -43,7 +43,7 @@ 1, 1 ], - "name": "constructor-call.js", + "filepath": "constructor-call.js", "end": [ 1, 29 @@ -60,7 +60,7 @@ 2, 1 ], - "name": "constructor-call.js", + "filepath": "constructor-call.js", "end": [ 2, 27 @@ -77,9 +77,9 @@ "filePaths": [ "constructor-call.js" ], - "sha1": "c84bb50f8570d3b7620847bb6e53e5164da5dc97", + "sha1": "ab9ab388d28ec6986921e04ab6efb34e293a00f3", "gitDir": "test/corpus/repos/javascript", - "sha2": "f95378398761e820b287651f61214cdaa4d087dd" + "sha2": "60d26544387b8eb9bc94b7e9d2427f9ec157b988" } ,{ "testCaseDescription": "javascript-constructor-call-delete-insert-test", @@ -94,7 +94,7 @@ 1, 21 ], - "name": "constructor-call.js", + "filepath": "constructor-call.js", "end": [ 1, 28 @@ -105,7 +105,7 @@ 1, 21 ], - "name": "constructor-call.js", + "filepath": "constructor-call.js", "end": [ 1, 26 @@ -123,9 +123,9 @@ "filePaths": [ "constructor-call.js" ], - "sha1": "f95378398761e820b287651f61214cdaa4d087dd", + "sha1": "60d26544387b8eb9bc94b7e9d2427f9ec157b988", "gitDir": "test/corpus/repos/javascript", - "sha2": "a24d6951b26950920f325e14e492a751fd96c459" + "sha2": "bc333c04253857d7a38f59e4d51778ba72d49d23" } ,{ "testCaseDescription": "javascript-constructor-call-replacement-test", @@ -140,7 +140,7 @@ 1, 21 ], - "name": "constructor-call.js", + "filepath": "constructor-call.js", "end": [ 1, 26 @@ -151,7 +151,7 @@ 1, 21 ], - "name": "constructor-call.js", + "filepath": "constructor-call.js", "end": [ 1, 28 @@ -169,9 +169,9 @@ "filePaths": [ "constructor-call.js" ], - "sha1": "a24d6951b26950920f325e14e492a751fd96c459", + "sha1": "bc333c04253857d7a38f59e4d51778ba72d49d23", "gitDir": "test/corpus/repos/javascript", - "sha2": "c8e18957750cdeed01b76272ae9dece10cc92bf4" + "sha2": "43543815e5d35f610e76d9b8b03095b6b989dc14" } ,{ "testCaseDescription": "javascript-constructor-call-delete-replacement-test", @@ -185,7 +185,7 @@ 1, 1 ], - "name": "constructor-call.js", + "filepath": "constructor-call.js", "end": [ 1, 29 @@ -202,7 +202,7 @@ 2, 1 ], - "name": "constructor-call.js", + "filepath": "constructor-call.js", "end": [ 2, 27 @@ -219,7 +219,7 @@ 2, 1 ], - "name": "constructor-call.js", + "filepath": "constructor-call.js", "end": [ 2, 29 @@ -236,9 +236,9 @@ "filePaths": [ "constructor-call.js" ], - "sha1": "c8e18957750cdeed01b76272ae9dece10cc92bf4", + "sha1": "43543815e5d35f610e76d9b8b03095b6b989dc14", "gitDir": "test/corpus/repos/javascript", - "sha2": "9be694183bf6de1655a6be394bf43f07f90b1bef" + "sha2": "4afe412c3a12b5fbbc0fdec59dbfd226f1c9d6ff" } ,{ "testCaseDescription": "javascript-constructor-call-delete-test", @@ -252,7 +252,7 @@ 1, 1 ], - "name": "constructor-call.js", + "filepath": "constructor-call.js", "end": [ 1, 27 @@ -269,9 +269,9 @@ "filePaths": [ "constructor-call.js" ], - "sha1": "9be694183bf6de1655a6be394bf43f07f90b1bef", + "sha1": "4afe412c3a12b5fbbc0fdec59dbfd226f1c9d6ff", "gitDir": "test/corpus/repos/javascript", - "sha2": "cbfcfc8f787243ede41b2cc3703a90986c2cbd64" + "sha2": "7907893594f652b89f2f63f4186ee6cd3e9a4a62" } ,{ "testCaseDescription": "javascript-constructor-call-delete-rest-test", @@ -285,7 +285,7 @@ 1, 1 ], - "name": "constructor-call.js", + "filepath": "constructor-call.js", "end": [ 1, 29 @@ -302,7 +302,7 @@ "filePaths": [ "constructor-call.js" ], - "sha1": "cbfcfc8f787243ede41b2cc3703a90986c2cbd64", + "sha1": "7907893594f652b89f2f63f4186ee6cd3e9a4a62", "gitDir": "test/corpus/repos/javascript", - "sha2": "952d18ccd1d4413a1252458befbb6593253aa794" + "sha2": "3c0252908fc7ee20c686918ee278f446a5bd4e81" }] diff --git a/test/corpus/diff-summaries/javascript/delete-operator.json b/test/corpus/diff-summaries/javascript/delete-operator.json index 03be6125e..fc8ef6147 100644 --- a/test/corpus/diff-summaries/javascript/delete-operator.json +++ b/test/corpus/diff-summaries/javascript/delete-operator.json @@ -10,7 +10,7 @@ 1, 1 ], - "name": "delete-operator.js", + "filepath": "delete-operator.js", "end": [ 1, 21 @@ -27,9 +27,9 @@ "filePaths": [ "delete-operator.js" ], - "sha1": "1d2c6fd4f13c50341f68aa3be753d5748c072f12", + "sha1": "2d654a2cacf790c8f0ab170868208cde6e793878", "gitDir": "test/corpus/repos/javascript", - "sha2": "79d9ba3ad4cb2029c5a611275136bb722cdd1e16" + "sha2": "911ec8edb0613ff5aa63f558b2d243ecea22874d" } ,{ "testCaseDescription": "javascript-delete-operator-replacement-insert-test", @@ -43,7 +43,7 @@ 1, 1 ], - "name": "delete-operator.js", + "filepath": "delete-operator.js", "end": [ 1, 18 @@ -60,7 +60,7 @@ 2, 1 ], - "name": "delete-operator.js", + "filepath": "delete-operator.js", "end": [ 2, 21 @@ -77,9 +77,9 @@ "filePaths": [ "delete-operator.js" ], - "sha1": "79d9ba3ad4cb2029c5a611275136bb722cdd1e16", + "sha1": "911ec8edb0613ff5aa63f558b2d243ecea22874d", "gitDir": "test/corpus/repos/javascript", - "sha2": "92ece167d0e443f1ec929261dc1ec23c1373ef36" + "sha2": "abf565d8e53695f898d9a439367609750261d4fa" } ,{ "testCaseDescription": "javascript-delete-operator-delete-insert-test", @@ -94,7 +94,7 @@ 1, 1 ], - "name": "delete-operator.js", + "filepath": "delete-operator.js", "end": [ 1, 18 @@ -105,7 +105,7 @@ 1, 1 ], - "name": "delete-operator.js", + "filepath": "delete-operator.js", "end": [ 1, 21 @@ -123,9 +123,9 @@ "filePaths": [ "delete-operator.js" ], - "sha1": "92ece167d0e443f1ec929261dc1ec23c1373ef36", + "sha1": "abf565d8e53695f898d9a439367609750261d4fa", "gitDir": "test/corpus/repos/javascript", - "sha2": "e5f4a3669771a2906494327404537d35b5a64586" + "sha2": "7c0122c9eb46c1ffa31c29bc8491a2b19de5dc57" } ,{ "testCaseDescription": "javascript-delete-operator-replacement-test", @@ -140,7 +140,7 @@ 1, 1 ], - "name": "delete-operator.js", + "filepath": "delete-operator.js", "end": [ 1, 21 @@ -151,7 +151,7 @@ 1, 1 ], - "name": "delete-operator.js", + "filepath": "delete-operator.js", "end": [ 1, 18 @@ -169,9 +169,9 @@ "filePaths": [ "delete-operator.js" ], - "sha1": "e5f4a3669771a2906494327404537d35b5a64586", + "sha1": "7c0122c9eb46c1ffa31c29bc8491a2b19de5dc57", "gitDir": "test/corpus/repos/javascript", - "sha2": "a41fba80ce5541212c1d9e857994ff32798ffc5b" + "sha2": "5dd8d34825be8fdab5d3c9d287a2998bc1764aa9" } ,{ "testCaseDescription": "javascript-delete-operator-delete-replacement-test", @@ -185,7 +185,7 @@ 1, 1 ], - "name": "delete-operator.js", + "filepath": "delete-operator.js", "end": [ 1, 18 @@ -202,7 +202,7 @@ 2, 1 ], - "name": "delete-operator.js", + "filepath": "delete-operator.js", "end": [ 2, 21 @@ -219,7 +219,7 @@ 2, 1 ], - "name": "delete-operator.js", + "filepath": "delete-operator.js", "end": [ 2, 18 @@ -236,9 +236,9 @@ "filePaths": [ "delete-operator.js" ], - "sha1": "a41fba80ce5541212c1d9e857994ff32798ffc5b", + "sha1": "5dd8d34825be8fdab5d3c9d287a2998bc1764aa9", "gitDir": "test/corpus/repos/javascript", - "sha2": "53fc1797fbb60e86e31bc8700953d1226c3c5378" + "sha2": "22314015087cc8a2cd1833112b67c2281ee73a50" } ,{ "testCaseDescription": "javascript-delete-operator-delete-test", @@ -252,7 +252,7 @@ 1, 1 ], - "name": "delete-operator.js", + "filepath": "delete-operator.js", "end": [ 1, 21 @@ -269,9 +269,9 @@ "filePaths": [ "delete-operator.js" ], - "sha1": "53fc1797fbb60e86e31bc8700953d1226c3c5378", + "sha1": "22314015087cc8a2cd1833112b67c2281ee73a50", "gitDir": "test/corpus/repos/javascript", - "sha2": "2df353078b8e0e73d9bc954808c567675203a143" + "sha2": "ece8d1a2f34fa2f9ae2f23ce14ec9f9f51b7c3fb" } ,{ "testCaseDescription": "javascript-delete-operator-delete-rest-test", @@ -285,7 +285,7 @@ 1, 1 ], - "name": "delete-operator.js", + "filepath": "delete-operator.js", "end": [ 1, 18 @@ -302,7 +302,7 @@ "filePaths": [ "delete-operator.js" ], - "sha1": "2df353078b8e0e73d9bc954808c567675203a143", + "sha1": "ece8d1a2f34fa2f9ae2f23ce14ec9f9f51b7c3fb", "gitDir": "test/corpus/repos/javascript", - "sha2": "f8fceed82b3d3f5189fd21d8dd7a5589c803ba0e" + "sha2": "8b7f1531572719818f5f5e3192046fa76b9f9124" }] diff --git a/test/corpus/diff-summaries/javascript/do-while-statement.json b/test/corpus/diff-summaries/javascript/do-while-statement.json index 7ea918035..109fd9c66 100644 --- a/test/corpus/diff-summaries/javascript/do-while-statement.json +++ b/test/corpus/diff-summaries/javascript/do-while-statement.json @@ -10,7 +10,7 @@ 1, 1 ], - "name": "do-while-statement.js", + "filepath": "do-while-statement.js", "end": [ 1, 42 @@ -27,9 +27,9 @@ "filePaths": [ "do-while-statement.js" ], - "sha1": "ea67bdfe9d16bfb0ba0858898f969294740b84fb", + "sha1": "278cfada4c53846b0d6ee921f9bbdc9bb113dd87", "gitDir": "test/corpus/repos/javascript", - "sha2": "1edeabe5a69e92387c0327d8782bfed7afe44ca0" + "sha2": "1a60cfc47d4344acefcbff2ddb6ad31bc6e30c55" } ,{ "testCaseDescription": "javascript-do-while-statement-replacement-insert-test", @@ -43,7 +43,7 @@ 1, 1 ], - "name": "do-while-statement.js", + "filepath": "do-while-statement.js", "end": [ 1, 48 @@ -60,7 +60,7 @@ 2, 1 ], - "name": "do-while-statement.js", + "filepath": "do-while-statement.js", "end": [ 2, 42 @@ -77,9 +77,9 @@ "filePaths": [ "do-while-statement.js" ], - "sha1": "1edeabe5a69e92387c0327d8782bfed7afe44ca0", + "sha1": "1a60cfc47d4344acefcbff2ddb6ad31bc6e30c55", "gitDir": "test/corpus/repos/javascript", - "sha2": "95cef4798ecd89a3a1756f9804ae3c0fa66002b9" + "sha2": "782fc10aa63c3458ae37c3a7c36a2de6207eb3e8" } ,{ "testCaseDescription": "javascript-do-while-statement-delete-insert-test", @@ -94,7 +94,7 @@ 1, 18 ], - "name": "do-while-statement.js", + "filepath": "do-while-statement.js", "end": [ 1, 29 @@ -105,7 +105,7 @@ 1, 18 ], - "name": "do-while-statement.js", + "filepath": "do-while-statement.js", "end": [ 1, 24 @@ -124,7 +124,7 @@ 1, 41 ], - "name": "do-while-statement.js", + "filepath": "do-while-statement.js", "end": [ 1, 46 @@ -135,7 +135,7 @@ 1, 36 ], - "name": "do-while-statement.js", + "filepath": "do-while-statement.js", "end": [ 1, 40 @@ -153,9 +153,9 @@ "filePaths": [ "do-while-statement.js" ], - "sha1": "95cef4798ecd89a3a1756f9804ae3c0fa66002b9", + "sha1": "782fc10aa63c3458ae37c3a7c36a2de6207eb3e8", "gitDir": "test/corpus/repos/javascript", - "sha2": "fe98c3543d4760b39db8064ba952a382afe9a3b7" + "sha2": "73284498ee1b90a351fa3b843265020803cdda0b" } ,{ "testCaseDescription": "javascript-do-while-statement-replacement-test", @@ -170,7 +170,7 @@ 1, 18 ], - "name": "do-while-statement.js", + "filepath": "do-while-statement.js", "end": [ 1, 24 @@ -181,7 +181,7 @@ 1, 18 ], - "name": "do-while-statement.js", + "filepath": "do-while-statement.js", "end": [ 1, 29 @@ -200,7 +200,7 @@ 1, 36 ], - "name": "do-while-statement.js", + "filepath": "do-while-statement.js", "end": [ 1, 40 @@ -211,7 +211,7 @@ 1, 41 ], - "name": "do-while-statement.js", + "filepath": "do-while-statement.js", "end": [ 1, 46 @@ -229,9 +229,9 @@ "filePaths": [ "do-while-statement.js" ], - "sha1": "fe98c3543d4760b39db8064ba952a382afe9a3b7", + "sha1": "73284498ee1b90a351fa3b843265020803cdda0b", "gitDir": "test/corpus/repos/javascript", - "sha2": "32e82efe60602edf29f95d10568c93cbd8f6d789" + "sha2": "06b3b39789f7cb079ad2aa33ae5963a6e46139c0" } ,{ "testCaseDescription": "javascript-do-while-statement-delete-replacement-test", @@ -245,7 +245,7 @@ 1, 1 ], - "name": "do-while-statement.js", + "filepath": "do-while-statement.js", "end": [ 1, 48 @@ -262,7 +262,7 @@ 2, 1 ], - "name": "do-while-statement.js", + "filepath": "do-while-statement.js", "end": [ 2, 42 @@ -279,7 +279,7 @@ 2, 1 ], - "name": "do-while-statement.js", + "filepath": "do-while-statement.js", "end": [ 2, 48 @@ -296,9 +296,9 @@ "filePaths": [ "do-while-statement.js" ], - "sha1": "32e82efe60602edf29f95d10568c93cbd8f6d789", + "sha1": "06b3b39789f7cb079ad2aa33ae5963a6e46139c0", "gitDir": "test/corpus/repos/javascript", - "sha2": "c7b0f597290d3b8a918a0c60dfed1fe05e9af91a" + "sha2": "b7ccb5198f3ec6faabda797181bc4e20aac3ae57" } ,{ "testCaseDescription": "javascript-do-while-statement-delete-test", @@ -312,7 +312,7 @@ 1, 1 ], - "name": "do-while-statement.js", + "filepath": "do-while-statement.js", "end": [ 1, 42 @@ -329,9 +329,9 @@ "filePaths": [ "do-while-statement.js" ], - "sha1": "c7b0f597290d3b8a918a0c60dfed1fe05e9af91a", + "sha1": "b7ccb5198f3ec6faabda797181bc4e20aac3ae57", "gitDir": "test/corpus/repos/javascript", - "sha2": "e0a76f9216bff7d64d708ad50a33d408ef885d55" + "sha2": "e0957bfb2c4aa997cc3f6b023363af2e7c3f718d" } ,{ "testCaseDescription": "javascript-do-while-statement-delete-rest-test", @@ -345,7 +345,7 @@ 1, 1 ], - "name": "do-while-statement.js", + "filepath": "do-while-statement.js", "end": [ 1, 48 @@ -362,7 +362,7 @@ "filePaths": [ "do-while-statement.js" ], - "sha1": "e0a76f9216bff7d64d708ad50a33d408ef885d55", + "sha1": "e0957bfb2c4aa997cc3f6b023363af2e7c3f718d", "gitDir": "test/corpus/repos/javascript", - "sha2": "fd292d1b33fb3253b0d0f66bae29de22c247d85c" + "sha2": "886cb49f75e2f0c0b4a7bd489323d02c708e28d2" }] diff --git a/test/corpus/diff-summaries/javascript/false.json b/test/corpus/diff-summaries/javascript/false.json index 3c56aae07..72ebb7b76 100644 --- a/test/corpus/diff-summaries/javascript/false.json +++ b/test/corpus/diff-summaries/javascript/false.json @@ -10,7 +10,7 @@ 1, 1 ], - "name": "false.js", + "filepath": "false.js", "end": [ 1, 6 @@ -27,9 +27,9 @@ "filePaths": [ "false.js" ], - "sha1": "d72ebc215a9377983c2463fd424f608320626141", + "sha1": "35b84d898e391652677c90f2c3e519f23cd51d8b", "gitDir": "test/corpus/repos/javascript", - "sha2": "240ba155f4a0d96494076ac592383350d2743fb6" + "sha2": "2deabe550fd6732848c41da726b757944d3cc38f" } ,{ "testCaseDescription": "javascript-false-replacement-insert-test", @@ -43,7 +43,7 @@ 1, 1 ], - "name": "false.js", + "filepath": "false.js", "end": [ 1, 14 @@ -60,7 +60,7 @@ 2, 1 ], - "name": "false.js", + "filepath": "false.js", "end": [ 2, 6 @@ -77,9 +77,9 @@ "filePaths": [ "false.js" ], - "sha1": "240ba155f4a0d96494076ac592383350d2743fb6", + "sha1": "2deabe550fd6732848c41da726b757944d3cc38f", "gitDir": "test/corpus/repos/javascript", - "sha2": "754a612c9706e0a510e018e4c450fe4fe1187efc" + "sha2": "273c03d19860cfabe4e4f4d02fb9a3975a2d7a13" } ,{ "testCaseDescription": "javascript-false-delete-insert-test", @@ -93,7 +93,7 @@ 1, 1 ], - "name": "false.js", + "filepath": "false.js", "end": [ 1, 6 @@ -110,7 +110,7 @@ 1, 1 ], - "name": "false.js", + "filepath": "false.js", "end": [ 1, 14 @@ -127,9 +127,9 @@ "filePaths": [ "false.js" ], - "sha1": "754a612c9706e0a510e018e4c450fe4fe1187efc", + "sha1": "273c03d19860cfabe4e4f4d02fb9a3975a2d7a13", "gitDir": "test/corpus/repos/javascript", - "sha2": "0bc6cba1b1ef9e8b8cabc8113a015441a7f8b690" + "sha2": "3a20072e9663c17abf1f245b3a2a006bcb1a15b1" } ,{ "testCaseDescription": "javascript-false-replacement-test", @@ -143,7 +143,7 @@ 1, 1 ], - "name": "false.js", + "filepath": "false.js", "end": [ 1, 14 @@ -160,7 +160,7 @@ 1, 1 ], - "name": "false.js", + "filepath": "false.js", "end": [ 1, 6 @@ -177,9 +177,9 @@ "filePaths": [ "false.js" ], - "sha1": "0bc6cba1b1ef9e8b8cabc8113a015441a7f8b690", + "sha1": "3a20072e9663c17abf1f245b3a2a006bcb1a15b1", "gitDir": "test/corpus/repos/javascript", - "sha2": "8a8271e57bb0d9af3a3137170449e27344a574fb" + "sha2": "bb17ec8db2f38d429af2cafce85cdab8e38298b7" } ,{ "testCaseDescription": "javascript-false-delete-replacement-test", @@ -193,7 +193,7 @@ 1, 1 ], - "name": "false.js", + "filepath": "false.js", "end": [ 1, 14 @@ -210,7 +210,7 @@ 2, 1 ], - "name": "false.js", + "filepath": "false.js", "end": [ 2, 6 @@ -227,7 +227,7 @@ 2, 1 ], - "name": "false.js", + "filepath": "false.js", "end": [ 2, 14 @@ -244,9 +244,9 @@ "filePaths": [ "false.js" ], - "sha1": "8a8271e57bb0d9af3a3137170449e27344a574fb", + "sha1": "bb17ec8db2f38d429af2cafce85cdab8e38298b7", "gitDir": "test/corpus/repos/javascript", - "sha2": "94d9fd3e963a5ff7aecd77f21e25e423a0d991bf" + "sha2": "025f0d4a55f4138986e84edd5401728dd27461ca" } ,{ "testCaseDescription": "javascript-false-delete-test", @@ -260,7 +260,7 @@ 1, 1 ], - "name": "false.js", + "filepath": "false.js", "end": [ 1, 6 @@ -277,9 +277,9 @@ "filePaths": [ "false.js" ], - "sha1": "94d9fd3e963a5ff7aecd77f21e25e423a0d991bf", + "sha1": "025f0d4a55f4138986e84edd5401728dd27461ca", "gitDir": "test/corpus/repos/javascript", - "sha2": "e1b3d5f5c03327df610744915e4ae73b5e2af1d0" + "sha2": "38968177a75289f1b25c67c7c1e95f73c28e0aef" } ,{ "testCaseDescription": "javascript-false-delete-rest-test", @@ -293,7 +293,7 @@ 1, 1 ], - "name": "false.js", + "filepath": "false.js", "end": [ 1, 14 @@ -310,7 +310,7 @@ "filePaths": [ "false.js" ], - "sha1": "e1b3d5f5c03327df610744915e4ae73b5e2af1d0", + "sha1": "38968177a75289f1b25c67c7c1e95f73c28e0aef", "gitDir": "test/corpus/repos/javascript", - "sha2": "a73251e778f05b8cbe501d5f6ea0c483640ced20" + "sha2": "986d0ecda39fda27a3351e2a332bda7d107a5665" }] diff --git a/test/corpus/diff-summaries/javascript/for-in-statement.json b/test/corpus/diff-summaries/javascript/for-in-statement.json index e63d5e4b5..b67fdacdb 100644 --- a/test/corpus/diff-summaries/javascript/for-in-statement.json +++ b/test/corpus/diff-summaries/javascript/for-in-statement.json @@ -10,7 +10,7 @@ 1, 1 ], - "name": "for-in-statement.js", + "filepath": "for-in-statement.js", "end": [ 1, 35 @@ -27,9 +27,9 @@ "filePaths": [ "for-in-statement.js" ], - "sha1": "7fe4e0b214260f0482129909a00b5146e3bfc1da", + "sha1": "67b05aa41fe5238680406e84c8b72407f7406e69", "gitDir": "test/corpus/repos/javascript", - "sha2": "6bab84255f645c5440731291f1b3e2405e608dcb" + "sha2": "8d986a0350165810bbfd440f8d5ef75505d8ee83" } ,{ "testCaseDescription": "javascript-for-in-statement-replacement-insert-test", @@ -43,7 +43,7 @@ 1, 1 ], - "name": "for-in-statement.js", + "filepath": "for-in-statement.js", "end": [ 1, 32 @@ -60,7 +60,7 @@ 2, 1 ], - "name": "for-in-statement.js", + "filepath": "for-in-statement.js", "end": [ 2, 35 @@ -77,9 +77,9 @@ "filePaths": [ "for-in-statement.js" ], - "sha1": "6bab84255f645c5440731291f1b3e2405e608dcb", + "sha1": "8d986a0350165810bbfd440f8d5ef75505d8ee83", "gitDir": "test/corpus/repos/javascript", - "sha2": "229e0057d54bdb3dddabd1b1f4c5b520dc7b5617" + "sha2": "4fa5a85de288d899164123daa88b0d316f687bcc" } ,{ "testCaseDescription": "javascript-for-in-statement-delete-insert-test", @@ -94,7 +94,7 @@ 1, 6 ], - "name": "for-in-statement.js", + "filepath": "for-in-statement.js", "end": [ 1, 10 @@ -105,7 +105,7 @@ 1, 6 ], - "name": "for-in-statement.js", + "filepath": "for-in-statement.js", "end": [ 1, 11 @@ -124,7 +124,7 @@ 1, 14 ], - "name": "for-in-statement.js", + "filepath": "for-in-statement.js", "end": [ 1, 19 @@ -135,7 +135,7 @@ 1, 15 ], - "name": "for-in-statement.js", + "filepath": "for-in-statement.js", "end": [ 1, 21 @@ -154,7 +154,7 @@ 1, 23 ], - "name": "for-in-statement.js", + "filepath": "for-in-statement.js", "end": [ 1, 27 @@ -165,7 +165,7 @@ 1, 25 ], - "name": "for-in-statement.js", + "filepath": "for-in-statement.js", "end": [ 1, 30 @@ -183,9 +183,9 @@ "filePaths": [ "for-in-statement.js" ], - "sha1": "229e0057d54bdb3dddabd1b1f4c5b520dc7b5617", + "sha1": "4fa5a85de288d899164123daa88b0d316f687bcc", "gitDir": "test/corpus/repos/javascript", - "sha2": "db98b8a60e7b0eeac50e68d6b4b5c8d4f557ca9e" + "sha2": "14b160a2b5a3be948b087c811d020b788b30fc70" } ,{ "testCaseDescription": "javascript-for-in-statement-replacement-test", @@ -200,7 +200,7 @@ 1, 6 ], - "name": "for-in-statement.js", + "filepath": "for-in-statement.js", "end": [ 1, 11 @@ -211,7 +211,7 @@ 1, 6 ], - "name": "for-in-statement.js", + "filepath": "for-in-statement.js", "end": [ 1, 10 @@ -230,7 +230,7 @@ 1, 15 ], - "name": "for-in-statement.js", + "filepath": "for-in-statement.js", "end": [ 1, 21 @@ -241,7 +241,7 @@ 1, 14 ], - "name": "for-in-statement.js", + "filepath": "for-in-statement.js", "end": [ 1, 19 @@ -260,7 +260,7 @@ 1, 25 ], - "name": "for-in-statement.js", + "filepath": "for-in-statement.js", "end": [ 1, 30 @@ -271,7 +271,7 @@ 1, 23 ], - "name": "for-in-statement.js", + "filepath": "for-in-statement.js", "end": [ 1, 27 @@ -289,9 +289,9 @@ "filePaths": [ "for-in-statement.js" ], - "sha1": "db98b8a60e7b0eeac50e68d6b4b5c8d4f557ca9e", + "sha1": "14b160a2b5a3be948b087c811d020b788b30fc70", "gitDir": "test/corpus/repos/javascript", - "sha2": "35dffb6c595ca8dbd5e2d557271f29b573177e79" + "sha2": "be5ab118cb3bb4854f1d48e08f3a9deece3edf47" } ,{ "testCaseDescription": "javascript-for-in-statement-delete-replacement-test", @@ -305,7 +305,7 @@ 1, 1 ], - "name": "for-in-statement.js", + "filepath": "for-in-statement.js", "end": [ 1, 32 @@ -322,7 +322,7 @@ 2, 1 ], - "name": "for-in-statement.js", + "filepath": "for-in-statement.js", "end": [ 2, 35 @@ -339,7 +339,7 @@ 2, 1 ], - "name": "for-in-statement.js", + "filepath": "for-in-statement.js", "end": [ 2, 32 @@ -356,9 +356,9 @@ "filePaths": [ "for-in-statement.js" ], - "sha1": "35dffb6c595ca8dbd5e2d557271f29b573177e79", + "sha1": "be5ab118cb3bb4854f1d48e08f3a9deece3edf47", "gitDir": "test/corpus/repos/javascript", - "sha2": "ad88456eafdc0e88fec2dc3677bfcc5c7f37c310" + "sha2": "048bd147196ebd52cbf8fab2c210a81c096ff78a" } ,{ "testCaseDescription": "javascript-for-in-statement-delete-test", @@ -372,7 +372,7 @@ 1, 1 ], - "name": "for-in-statement.js", + "filepath": "for-in-statement.js", "end": [ 1, 35 @@ -389,9 +389,9 @@ "filePaths": [ "for-in-statement.js" ], - "sha1": "ad88456eafdc0e88fec2dc3677bfcc5c7f37c310", + "sha1": "048bd147196ebd52cbf8fab2c210a81c096ff78a", "gitDir": "test/corpus/repos/javascript", - "sha2": "13399a918cf13accf13f9001b70995b677ba4467" + "sha2": "eae38d235d51afd7ec9c0c9ceff966f3a1b07e7a" } ,{ "testCaseDescription": "javascript-for-in-statement-delete-rest-test", @@ -405,7 +405,7 @@ 1, 1 ], - "name": "for-in-statement.js", + "filepath": "for-in-statement.js", "end": [ 1, 32 @@ -422,7 +422,7 @@ "filePaths": [ "for-in-statement.js" ], - "sha1": "13399a918cf13accf13f9001b70995b677ba4467", + "sha1": "eae38d235d51afd7ec9c0c9ceff966f3a1b07e7a", "gitDir": "test/corpus/repos/javascript", - "sha2": "ff9c3e1416340f9c41efe59880ae44b658ff4bf3" + "sha2": "656605a9a5331108b78a2e26adccd905a1d0c760" }] diff --git a/test/corpus/diff-summaries/javascript/for-loop-with-in-statement.json b/test/corpus/diff-summaries/javascript/for-loop-with-in-statement.json index b7b5dc45d..59e10eebd 100644 --- a/test/corpus/diff-summaries/javascript/for-loop-with-in-statement.json +++ b/test/corpus/diff-summaries/javascript/for-loop-with-in-statement.json @@ -10,7 +10,7 @@ 1, 1 ], - "name": "for-loop-with-in-statement.js", + "filepath": "for-loop-with-in-statement.js", "end": [ 1, 63 @@ -27,9 +27,9 @@ "filePaths": [ "for-loop-with-in-statement.js" ], - "sha1": "b0363eb07d0284130aab04183573dcd31fa7f221", + "sha1": "2713efa83046b111f22730202b3db5213732e388", "gitDir": "test/corpus/repos/javascript", - "sha2": "bd70642d89f84aa72ff6781a2b22c82b345ac1d5" + "sha2": "d0d4e80ab5e1000adc85ca2ae3ef5c308ba058e5" } ,{ "testCaseDescription": "javascript-for-loop-with-in-statement-replacement-insert-test", @@ -43,7 +43,7 @@ 1, 1 ], - "name": "for-loop-with-in-statement.js", + "filepath": "for-loop-with-in-statement.js", "end": [ 1, 73 @@ -60,7 +60,7 @@ 2, 1 ], - "name": "for-loop-with-in-statement.js", + "filepath": "for-loop-with-in-statement.js", "end": [ 2, 63 @@ -77,9 +77,9 @@ "filePaths": [ "for-loop-with-in-statement.js" ], - "sha1": "bd70642d89f84aa72ff6781a2b22c82b345ac1d5", + "sha1": "d0d4e80ab5e1000adc85ca2ae3ef5c308ba058e5", "gitDir": "test/corpus/repos/javascript", - "sha2": "337a282c5bfdde568b4b1431a6259fd1e187d897" + "sha2": "22b27eed20a4708f57655fac41373782e765bdd9" } ,{ "testCaseDescription": "javascript-for-loop-with-in-statement-delete-insert-test", @@ -94,7 +94,7 @@ 1, 6 ], - "name": "for-loop-with-in-statement.js", + "filepath": "for-loop-with-in-statement.js", "end": [ 1, 14 @@ -105,7 +105,7 @@ 1, 6 ], - "name": "for-loop-with-in-statement.js", + "filepath": "for-loop-with-in-statement.js", "end": [ 1, 9 @@ -124,7 +124,7 @@ 1, 52 ], - "name": "for-loop-with-in-statement.js", + "filepath": "for-loop-with-in-statement.js", "end": [ 1, 68 @@ -135,7 +135,7 @@ 1, 47 ], - "name": "for-loop-with-in-statement.js", + "filepath": "for-loop-with-in-statement.js", "end": [ 1, 58 @@ -153,9 +153,9 @@ "filePaths": [ "for-loop-with-in-statement.js" ], - "sha1": "337a282c5bfdde568b4b1431a6259fd1e187d897", + "sha1": "22b27eed20a4708f57655fac41373782e765bdd9", "gitDir": "test/corpus/repos/javascript", - "sha2": "b6039e1333c1772e592e7dc27a94de22b1323bb5" + "sha2": "752138dea1fa4b37d532668dfdb80c1de9dbe984" } ,{ "testCaseDescription": "javascript-for-loop-with-in-statement-replacement-test", @@ -170,7 +170,7 @@ 1, 6 ], - "name": "for-loop-with-in-statement.js", + "filepath": "for-loop-with-in-statement.js", "end": [ 1, 9 @@ -181,7 +181,7 @@ 1, 6 ], - "name": "for-loop-with-in-statement.js", + "filepath": "for-loop-with-in-statement.js", "end": [ 1, 14 @@ -200,7 +200,7 @@ 1, 47 ], - "name": "for-loop-with-in-statement.js", + "filepath": "for-loop-with-in-statement.js", "end": [ 1, 58 @@ -211,7 +211,7 @@ 1, 52 ], - "name": "for-loop-with-in-statement.js", + "filepath": "for-loop-with-in-statement.js", "end": [ 1, 68 @@ -229,9 +229,9 @@ "filePaths": [ "for-loop-with-in-statement.js" ], - "sha1": "b6039e1333c1772e592e7dc27a94de22b1323bb5", + "sha1": "752138dea1fa4b37d532668dfdb80c1de9dbe984", "gitDir": "test/corpus/repos/javascript", - "sha2": "0a764d4fa36759c678501ca540fc99713b41420a" + "sha2": "d4746a1fc6b915b1f3039637c8525ddd1fe3e7ea" } ,{ "testCaseDescription": "javascript-for-loop-with-in-statement-delete-replacement-test", @@ -245,7 +245,7 @@ 1, 1 ], - "name": "for-loop-with-in-statement.js", + "filepath": "for-loop-with-in-statement.js", "end": [ 1, 73 @@ -262,7 +262,7 @@ 2, 1 ], - "name": "for-loop-with-in-statement.js", + "filepath": "for-loop-with-in-statement.js", "end": [ 2, 63 @@ -279,7 +279,7 @@ 2, 1 ], - "name": "for-loop-with-in-statement.js", + "filepath": "for-loop-with-in-statement.js", "end": [ 2, 73 @@ -296,9 +296,9 @@ "filePaths": [ "for-loop-with-in-statement.js" ], - "sha1": "0a764d4fa36759c678501ca540fc99713b41420a", + "sha1": "d4746a1fc6b915b1f3039637c8525ddd1fe3e7ea", "gitDir": "test/corpus/repos/javascript", - "sha2": "9fa99c92ac72ad519a3b1f2b5d93a5537d435a92" + "sha2": "175e3c87a4f60bcc38fa14c26df38f489e34d707" } ,{ "testCaseDescription": "javascript-for-loop-with-in-statement-delete-test", @@ -312,7 +312,7 @@ 1, 1 ], - "name": "for-loop-with-in-statement.js", + "filepath": "for-loop-with-in-statement.js", "end": [ 1, 63 @@ -329,9 +329,9 @@ "filePaths": [ "for-loop-with-in-statement.js" ], - "sha1": "9fa99c92ac72ad519a3b1f2b5d93a5537d435a92", + "sha1": "175e3c87a4f60bcc38fa14c26df38f489e34d707", "gitDir": "test/corpus/repos/javascript", - "sha2": "cbc52bfd4415f0b6ade8e057dc28ea23bb4525de" + "sha2": "d683d2247eafa64957f62abd7cf4bddeccba9e48" } ,{ "testCaseDescription": "javascript-for-loop-with-in-statement-delete-rest-test", @@ -345,7 +345,7 @@ 1, 1 ], - "name": "for-loop-with-in-statement.js", + "filepath": "for-loop-with-in-statement.js", "end": [ 1, 73 @@ -362,7 +362,7 @@ "filePaths": [ "for-loop-with-in-statement.js" ], - "sha1": "cbc52bfd4415f0b6ade8e057dc28ea23bb4525de", + "sha1": "d683d2247eafa64957f62abd7cf4bddeccba9e48", "gitDir": "test/corpus/repos/javascript", - "sha2": "78d8fd6fdf97f596e0c6c4c7f4a6661bc3ffa357" + "sha2": "1775d9c8a22836c57a2a9883aac27bb0d16f14c4" }] diff --git a/test/corpus/diff-summaries/javascript/for-of-statement.json b/test/corpus/diff-summaries/javascript/for-of-statement.json index 8368ad1d4..a95954192 100644 --- a/test/corpus/diff-summaries/javascript/for-of-statement.json +++ b/test/corpus/diff-summaries/javascript/for-of-statement.json @@ -10,7 +10,7 @@ 1, 1 ], - "name": "for-of-statement.js", + "filepath": "for-of-statement.js", "end": [ 1, 43 @@ -27,9 +27,9 @@ "filePaths": [ "for-of-statement.js" ], - "sha1": "78d8fd6fdf97f596e0c6c4c7f4a6661bc3ffa357", + "sha1": "b38f26a221993704e5798100ceabd747335d0fa9", "gitDir": "test/corpus/repos/javascript", - "sha2": "70584f81e9913597b116943cebc3749db173209f" + "sha2": "c408953071aeb3ef68fdfa06b28d07a330e96954" } ,{ "testCaseDescription": "javascript-for-of-statement-replacement-insert-test", @@ -43,7 +43,7 @@ 1, 1 ], - "name": "for-of-statement.js", + "filepath": "for-of-statement.js", "end": [ 1, 46 @@ -60,7 +60,7 @@ 2, 1 ], - "name": "for-of-statement.js", + "filepath": "for-of-statement.js", "end": [ 2, 43 @@ -77,9 +77,9 @@ "filePaths": [ "for-of-statement.js" ], - "sha1": "70584f81e9913597b116943cebc3749db173209f", + "sha1": "c408953071aeb3ef68fdfa06b28d07a330e96954", "gitDir": "test/corpus/repos/javascript", - "sha2": "c45a6d3219e4221bd27fbee1b42e709cf8bd02c7" + "sha2": "677d1a58506fdf44613fd3806dd4ba364248c6b9" } ,{ "testCaseDescription": "javascript-for-of-statement-delete-insert-test", @@ -94,7 +94,7 @@ 1, 10 ], - "name": "for-of-statement.js", + "filepath": "for-of-statement.js", "end": [ 1, 15 @@ -105,7 +105,7 @@ 1, 10 ], - "name": "for-of-statement.js", + "filepath": "for-of-statement.js", "end": [ 1, 14 @@ -124,7 +124,7 @@ 1, 19 ], - "name": "for-of-statement.js", + "filepath": "for-of-statement.js", "end": [ 1, 25 @@ -135,7 +135,7 @@ 1, 18 ], - "name": "for-of-statement.js", + "filepath": "for-of-statement.js", "end": [ 1, 23 @@ -154,7 +154,7 @@ 1, 37 ], - "name": "for-of-statement.js", + "filepath": "for-of-statement.js", "end": [ 1, 42 @@ -165,7 +165,7 @@ 1, 35 ], - "name": "for-of-statement.js", + "filepath": "for-of-statement.js", "end": [ 1, 39 @@ -183,9 +183,9 @@ "filePaths": [ "for-of-statement.js" ], - "sha1": "c45a6d3219e4221bd27fbee1b42e709cf8bd02c7", + "sha1": "677d1a58506fdf44613fd3806dd4ba364248c6b9", "gitDir": "test/corpus/repos/javascript", - "sha2": "a5ca7dcb73c029d81d8d5dc393828d7d7674fbca" + "sha2": "9792430b37eff875b124bcc3bbc94d57846291ef" } ,{ "testCaseDescription": "javascript-for-of-statement-replacement-test", @@ -200,7 +200,7 @@ 1, 10 ], - "name": "for-of-statement.js", + "filepath": "for-of-statement.js", "end": [ 1, 14 @@ -211,7 +211,7 @@ 1, 10 ], - "name": "for-of-statement.js", + "filepath": "for-of-statement.js", "end": [ 1, 15 @@ -230,7 +230,7 @@ 1, 18 ], - "name": "for-of-statement.js", + "filepath": "for-of-statement.js", "end": [ 1, 23 @@ -241,7 +241,7 @@ 1, 19 ], - "name": "for-of-statement.js", + "filepath": "for-of-statement.js", "end": [ 1, 25 @@ -260,7 +260,7 @@ 1, 35 ], - "name": "for-of-statement.js", + "filepath": "for-of-statement.js", "end": [ 1, 39 @@ -271,7 +271,7 @@ 1, 37 ], - "name": "for-of-statement.js", + "filepath": "for-of-statement.js", "end": [ 1, 42 @@ -289,9 +289,9 @@ "filePaths": [ "for-of-statement.js" ], - "sha1": "a5ca7dcb73c029d81d8d5dc393828d7d7674fbca", + "sha1": "9792430b37eff875b124bcc3bbc94d57846291ef", "gitDir": "test/corpus/repos/javascript", - "sha2": "19da16ae29c9cfbc2a47cd92a14fb09c20408e22" + "sha2": "81efff7ba1789c1b3b4bdbc25f2b9b5101309d30" } ,{ "testCaseDescription": "javascript-for-of-statement-delete-replacement-test", @@ -305,7 +305,7 @@ 1, 1 ], - "name": "for-of-statement.js", + "filepath": "for-of-statement.js", "end": [ 1, 46 @@ -322,7 +322,7 @@ 2, 1 ], - "name": "for-of-statement.js", + "filepath": "for-of-statement.js", "end": [ 2, 43 @@ -339,7 +339,7 @@ 2, 1 ], - "name": "for-of-statement.js", + "filepath": "for-of-statement.js", "end": [ 2, 46 @@ -356,9 +356,9 @@ "filePaths": [ "for-of-statement.js" ], - "sha1": "19da16ae29c9cfbc2a47cd92a14fb09c20408e22", + "sha1": "81efff7ba1789c1b3b4bdbc25f2b9b5101309d30", "gitDir": "test/corpus/repos/javascript", - "sha2": "e0ae09c0a24fbf452fa08f5c08208846c7df9ce2" + "sha2": "df35312c2b45297aaed5e4839f725549848c7b82" } ,{ "testCaseDescription": "javascript-for-of-statement-delete-test", @@ -372,7 +372,7 @@ 1, 1 ], - "name": "for-of-statement.js", + "filepath": "for-of-statement.js", "end": [ 1, 43 @@ -389,9 +389,9 @@ "filePaths": [ "for-of-statement.js" ], - "sha1": "e0ae09c0a24fbf452fa08f5c08208846c7df9ce2", + "sha1": "df35312c2b45297aaed5e4839f725549848c7b82", "gitDir": "test/corpus/repos/javascript", - "sha2": "ed738907075661e8ce229daa60e004c416a5ddf2" + "sha2": "8a0a6e005f7bcce0b3062e9f8caa2d2ef3ba6ae3" } ,{ "testCaseDescription": "javascript-for-of-statement-delete-rest-test", @@ -405,7 +405,7 @@ 1, 1 ], - "name": "for-of-statement.js", + "filepath": "for-of-statement.js", "end": [ 1, 46 @@ -422,7 +422,7 @@ "filePaths": [ "for-of-statement.js" ], - "sha1": "ed738907075661e8ce229daa60e004c416a5ddf2", + "sha1": "8a0a6e005f7bcce0b3062e9f8caa2d2ef3ba6ae3", "gitDir": "test/corpus/repos/javascript", - "sha2": "536e58f01a1c35bfed654e16dc15d4b2636913b7" + "sha2": "db4ec278dbbc9246ae987c940db0f5423fb88871" }] diff --git a/test/corpus/diff-summaries/javascript/for-statement.json b/test/corpus/diff-summaries/javascript/for-statement.json index 641bada7e..f59b90d67 100644 --- a/test/corpus/diff-summaries/javascript/for-statement.json +++ b/test/corpus/diff-summaries/javascript/for-statement.json @@ -10,7 +10,7 @@ 1, 1 ], - "name": "for-statement.js", + "filepath": "for-statement.js", "end": [ 1, 45 @@ -27,9 +27,9 @@ "filePaths": [ "for-statement.js" ], - "sha1": "0f63f399f084244c4cfcd918876a8c5e659e8ade", + "sha1": "fc1d361b1694b921227229883c2315989acf8455", "gitDir": "test/corpus/repos/javascript", - "sha2": "7099da096426789e903a008322119184fe353667" + "sha2": "6bf0bfe48cc0d2dc5680e671a7dfdc0bbdb14ac1" } ,{ "testCaseDescription": "javascript-for-statement-replacement-insert-test", @@ -43,7 +43,7 @@ 1, 1 ], - "name": "for-statement.js", + "filepath": "for-statement.js", "end": [ 1, 46 @@ -60,7 +60,7 @@ 2, 1 ], - "name": "for-statement.js", + "filepath": "for-statement.js", "end": [ 2, 45 @@ -77,9 +77,9 @@ "filePaths": [ "for-statement.js" ], - "sha1": "7099da096426789e903a008322119184fe353667", + "sha1": "6bf0bfe48cc0d2dc5680e671a7dfdc0bbdb14ac1", "gitDir": "test/corpus/repos/javascript", - "sha2": "74f2e9af36fcd6da27f51ac28ae448b4265bbc35" + "sha2": "80626dc9bcf9100526cd65f801436000a33b2759" } ,{ "testCaseDescription": "javascript-for-statement-delete-insert-test", @@ -94,7 +94,7 @@ 1, 25 ], - "name": "for-statement.js", + "filepath": "for-statement.js", "end": [ 1, 28 @@ -105,7 +105,7 @@ 1, 25 ], - "name": "for-statement.js", + "filepath": "for-statement.js", "end": [ 1, 27 @@ -123,9 +123,9 @@ "filePaths": [ "for-statement.js" ], - "sha1": "74f2e9af36fcd6da27f51ac28ae448b4265bbc35", + "sha1": "80626dc9bcf9100526cd65f801436000a33b2759", "gitDir": "test/corpus/repos/javascript", - "sha2": "b01d035ff217d4670f859865b248f6d076181288" + "sha2": "bee9b2b1ab5bd735d4b2cf66ad8b416d8ac105fb" } ,{ "testCaseDescription": "javascript-for-statement-replacement-test", @@ -140,7 +140,7 @@ 1, 25 ], - "name": "for-statement.js", + "filepath": "for-statement.js", "end": [ 1, 27 @@ -151,7 +151,7 @@ 1, 25 ], - "name": "for-statement.js", + "filepath": "for-statement.js", "end": [ 1, 28 @@ -169,9 +169,9 @@ "filePaths": [ "for-statement.js" ], - "sha1": "b01d035ff217d4670f859865b248f6d076181288", + "sha1": "bee9b2b1ab5bd735d4b2cf66ad8b416d8ac105fb", "gitDir": "test/corpus/repos/javascript", - "sha2": "8182996a9a072de805b19ceb80bc6d39d8693537" + "sha2": "c6e611d821765070fe3599b8c40c855b8cc282ca" } ,{ "testCaseDescription": "javascript-for-statement-delete-replacement-test", @@ -185,7 +185,7 @@ 1, 1 ], - "name": "for-statement.js", + "filepath": "for-statement.js", "end": [ 1, 46 @@ -202,7 +202,7 @@ 2, 1 ], - "name": "for-statement.js", + "filepath": "for-statement.js", "end": [ 2, 45 @@ -219,7 +219,7 @@ 2, 1 ], - "name": "for-statement.js", + "filepath": "for-statement.js", "end": [ 2, 46 @@ -236,9 +236,9 @@ "filePaths": [ "for-statement.js" ], - "sha1": "8182996a9a072de805b19ceb80bc6d39d8693537", + "sha1": "c6e611d821765070fe3599b8c40c855b8cc282ca", "gitDir": "test/corpus/repos/javascript", - "sha2": "9f53049277b37934e3a5cdeb842cc1eb2db27042" + "sha2": "c0678538577423d271f95d1fbcb741ab582f1cc9" } ,{ "testCaseDescription": "javascript-for-statement-delete-test", @@ -252,7 +252,7 @@ 1, 1 ], - "name": "for-statement.js", + "filepath": "for-statement.js", "end": [ 1, 45 @@ -269,9 +269,9 @@ "filePaths": [ "for-statement.js" ], - "sha1": "9f53049277b37934e3a5cdeb842cc1eb2db27042", + "sha1": "c0678538577423d271f95d1fbcb741ab582f1cc9", "gitDir": "test/corpus/repos/javascript", - "sha2": "592a641594a1bed9a74e1a439ca9c437cd99e2c0" + "sha2": "dccac3dbb15f085cd4fd8a54860da2f6f3abd029" } ,{ "testCaseDescription": "javascript-for-statement-delete-rest-test", @@ -285,7 +285,7 @@ 1, 1 ], - "name": "for-statement.js", + "filepath": "for-statement.js", "end": [ 1, 46 @@ -302,7 +302,7 @@ "filePaths": [ "for-statement.js" ], - "sha1": "592a641594a1bed9a74e1a439ca9c437cd99e2c0", + "sha1": "dccac3dbb15f085cd4fd8a54860da2f6f3abd029", "gitDir": "test/corpus/repos/javascript", - "sha2": "7c328351e5e8debb38b46a45f43481581e438666" + "sha2": "9b8688cb6caa30dfa6f19c511e51aa17d8d4ffcb" }] diff --git a/test/corpus/diff-summaries/javascript/function-call-args.json b/test/corpus/diff-summaries/javascript/function-call-args.json index 4c3a4aa85..796727f60 100644 --- a/test/corpus/diff-summaries/javascript/function-call-args.json +++ b/test/corpus/diff-summaries/javascript/function-call-args.json @@ -10,7 +10,7 @@ 1, 1 ], - "name": "function-call-args.js", + "filepath": "function-call-args.js", "end": [ 1, 77 @@ -27,9 +27,9 @@ "filePaths": [ "function-call-args.js" ], - "sha1": "90687f3994b4645e5db5b97ec4da3502fbe9053d", + "sha1": "e834dcf08a889d6a14fee6a80a53109e2794c8f8", "gitDir": "test/corpus/repos/javascript", - "sha2": "aaad24da26976a73c6d19f8663d8b1643c4465b5" + "sha2": "3411414b4a6da0a0dd500b1560d5e9e460980e93" } ,{ "testCaseDescription": "javascript-function-call-args-replacement-insert-test", @@ -43,7 +43,7 @@ 1, 1 ], - "name": "function-call-args.js", + "filepath": "function-call-args.js", "end": [ 1, 83 @@ -60,7 +60,7 @@ 2, 1 ], - "name": "function-call-args.js", + "filepath": "function-call-args.js", "end": [ 2, 77 @@ -77,9 +77,9 @@ "filePaths": [ "function-call-args.js" ], - "sha1": "aaad24da26976a73c6d19f8663d8b1643c4465b5", + "sha1": "3411414b4a6da0a0dd500b1560d5e9e460980e93", "gitDir": "test/corpus/repos/javascript", - "sha2": "d461ca4c5b99ac714342ba5a97a8b19822abf355" + "sha2": "bcb9e9c202d8e29a3cf33bd48661e7743926fb80" } ,{ "testCaseDescription": "javascript-function-call-args-delete-insert-test", @@ -94,7 +94,7 @@ 1, 17 ], - "name": "function-call-args.js", + "filepath": "function-call-args.js", "end": [ 1, 30 @@ -105,7 +105,7 @@ 1, 17 ], - "name": "function-call-args.js", + "filepath": "function-call-args.js", "end": [ 1, 25 @@ -124,7 +124,7 @@ 1, 41 ], - "name": "function-call-args.js", + "filepath": "function-call-args.js", "end": [ 1, 42 @@ -135,7 +135,7 @@ 1, 36 ], - "name": "function-call-args.js", + "filepath": "function-call-args.js", "end": [ 1, 37 @@ -154,7 +154,7 @@ 1, 43 ], - "name": "function-call-args.js", + "filepath": "function-call-args.js", "end": [ 1, 44 @@ -165,7 +165,7 @@ 1, 38 ], - "name": "function-call-args.js", + "filepath": "function-call-args.js", "end": [ 1, 39 @@ -184,7 +184,7 @@ 1, 60 ], - "name": "function-call-args.js", + "filepath": "function-call-args.js", "end": [ 1, 61 @@ -195,7 +195,7 @@ 1, 55 ], - "name": "function-call-args.js", + "filepath": "function-call-args.js", "end": [ 1, 56 @@ -214,7 +214,7 @@ 1, 71 ], - "name": "function-call-args.js", + "filepath": "function-call-args.js", "end": [ 1, 72 @@ -225,7 +225,7 @@ 1, 66 ], - "name": "function-call-args.js", + "filepath": "function-call-args.js", "end": [ 1, 67 @@ -244,7 +244,7 @@ 1, 77 ], - "name": "function-call-args.js", + "filepath": "function-call-args.js", "end": [ 1, 82 @@ -255,7 +255,7 @@ 1, 72 ], - "name": "function-call-args.js", + "filepath": "function-call-args.js", "end": [ 1, 76 @@ -273,9 +273,9 @@ "filePaths": [ "function-call-args.js" ], - "sha1": "d461ca4c5b99ac714342ba5a97a8b19822abf355", + "sha1": "bcb9e9c202d8e29a3cf33bd48661e7743926fb80", "gitDir": "test/corpus/repos/javascript", - "sha2": "5f1e05fcea9ea246eced001a88fb7872c1ae5923" + "sha2": "a4c89b79d352f733e430d75f970cb999677f27f5" } ,{ "testCaseDescription": "javascript-function-call-args-replacement-test", @@ -290,7 +290,7 @@ 1, 17 ], - "name": "function-call-args.js", + "filepath": "function-call-args.js", "end": [ 1, 25 @@ -301,7 +301,7 @@ 1, 17 ], - "name": "function-call-args.js", + "filepath": "function-call-args.js", "end": [ 1, 30 @@ -320,7 +320,7 @@ 1, 36 ], - "name": "function-call-args.js", + "filepath": "function-call-args.js", "end": [ 1, 37 @@ -331,7 +331,7 @@ 1, 41 ], - "name": "function-call-args.js", + "filepath": "function-call-args.js", "end": [ 1, 42 @@ -350,7 +350,7 @@ 1, 38 ], - "name": "function-call-args.js", + "filepath": "function-call-args.js", "end": [ 1, 39 @@ -361,7 +361,7 @@ 1, 43 ], - "name": "function-call-args.js", + "filepath": "function-call-args.js", "end": [ 1, 44 @@ -380,7 +380,7 @@ 1, 55 ], - "name": "function-call-args.js", + "filepath": "function-call-args.js", "end": [ 1, 56 @@ -391,7 +391,7 @@ 1, 60 ], - "name": "function-call-args.js", + "filepath": "function-call-args.js", "end": [ 1, 61 @@ -410,7 +410,7 @@ 1, 66 ], - "name": "function-call-args.js", + "filepath": "function-call-args.js", "end": [ 1, 67 @@ -421,7 +421,7 @@ 1, 71 ], - "name": "function-call-args.js", + "filepath": "function-call-args.js", "end": [ 1, 72 @@ -440,7 +440,7 @@ 1, 72 ], - "name": "function-call-args.js", + "filepath": "function-call-args.js", "end": [ 1, 76 @@ -451,7 +451,7 @@ 1, 77 ], - "name": "function-call-args.js", + "filepath": "function-call-args.js", "end": [ 1, 82 @@ -469,9 +469,9 @@ "filePaths": [ "function-call-args.js" ], - "sha1": "5f1e05fcea9ea246eced001a88fb7872c1ae5923", + "sha1": "a4c89b79d352f733e430d75f970cb999677f27f5", "gitDir": "test/corpus/repos/javascript", - "sha2": "ec8b293cdef0a7d4fce7791690c010b170e64c87" + "sha2": "3091a06bd0f54664d9af8ca81912d11053770867" } ,{ "testCaseDescription": "javascript-function-call-args-delete-replacement-test", @@ -485,7 +485,7 @@ 1, 1 ], - "name": "function-call-args.js", + "filepath": "function-call-args.js", "end": [ 1, 83 @@ -502,7 +502,7 @@ 2, 1 ], - "name": "function-call-args.js", + "filepath": "function-call-args.js", "end": [ 2, 77 @@ -519,7 +519,7 @@ 2, 1 ], - "name": "function-call-args.js", + "filepath": "function-call-args.js", "end": [ 2, 83 @@ -536,9 +536,9 @@ "filePaths": [ "function-call-args.js" ], - "sha1": "ec8b293cdef0a7d4fce7791690c010b170e64c87", + "sha1": "3091a06bd0f54664d9af8ca81912d11053770867", "gitDir": "test/corpus/repos/javascript", - "sha2": "36858f5bcf436b803282fedf78c4c997ce3562a7" + "sha2": "75ed223e42469c6619a6e1c4dc582bd709ceb391" } ,{ "testCaseDescription": "javascript-function-call-args-delete-test", @@ -552,7 +552,7 @@ 1, 1 ], - "name": "function-call-args.js", + "filepath": "function-call-args.js", "end": [ 1, 77 @@ -569,9 +569,9 @@ "filePaths": [ "function-call-args.js" ], - "sha1": "36858f5bcf436b803282fedf78c4c997ce3562a7", + "sha1": "75ed223e42469c6619a6e1c4dc582bd709ceb391", "gitDir": "test/corpus/repos/javascript", - "sha2": "d31e105c5f3e4c14ac404da8d6ee605cebd47126" + "sha2": "0554bafc40337500d565c66e7d2e4adcbc2f6dbd" } ,{ "testCaseDescription": "javascript-function-call-args-delete-rest-test", @@ -585,7 +585,7 @@ 1, 1 ], - "name": "function-call-args.js", + "filepath": "function-call-args.js", "end": [ 1, 83 @@ -602,7 +602,7 @@ "filePaths": [ "function-call-args.js" ], - "sha1": "d31e105c5f3e4c14ac404da8d6ee605cebd47126", + "sha1": "0554bafc40337500d565c66e7d2e4adcbc2f6dbd", "gitDir": "test/corpus/repos/javascript", - "sha2": "f110a993d59a58f31e4b09bd46734026c4fdcc60" + "sha2": "6bac47f01ea270d54850d73f02855a9b88d9e85a" }] diff --git a/test/corpus/diff-summaries/javascript/function-call.json b/test/corpus/diff-summaries/javascript/function-call.json index b4c808d74..136de4316 100644 --- a/test/corpus/diff-summaries/javascript/function-call.json +++ b/test/corpus/diff-summaries/javascript/function-call.json @@ -10,7 +10,7 @@ 1, 1 ], - "name": "function-call.js", + "filepath": "function-call.js", "end": [ 1, 27 @@ -27,9 +27,9 @@ "filePaths": [ "function-call.js" ], - "sha1": "bd29fccbe38961789cd724a6537993e68f491091", + "sha1": "41ecf2db3b34d290e3090049d67925f7635f2e56", "gitDir": "test/corpus/repos/javascript", - "sha2": "8f45c8caf64bcf2ecc371c0c865d25de1965ca81" + "sha2": "3b5480d253cbeae1d951b8eaf895af479e9820a8" } ,{ "testCaseDescription": "javascript-function-call-replacement-insert-test", @@ -43,7 +43,7 @@ 1, 1 ], - "name": "function-call.js", + "filepath": "function-call.js", "end": [ 1, 27 @@ -60,7 +60,7 @@ 2, 1 ], - "name": "function-call.js", + "filepath": "function-call.js", "end": [ 2, 27 @@ -77,9 +77,9 @@ "filePaths": [ "function-call.js" ], - "sha1": "8f45c8caf64bcf2ecc371c0c865d25de1965ca81", + "sha1": "3b5480d253cbeae1d951b8eaf895af479e9820a8", "gitDir": "test/corpus/repos/javascript", - "sha2": "3c90d6519f2134b74fb9393f42d42476d101b75a" + "sha2": "038fcd883cc64e100f5886954353987e996ebbcf" } ,{ "testCaseDescription": "javascript-function-call-delete-insert-test", @@ -94,7 +94,7 @@ 1, 20 ], - "name": "function-call.js", + "filepath": "function-call.js", "end": [ 1, 26 @@ -105,7 +105,7 @@ 1, 20 ], - "name": "function-call.js", + "filepath": "function-call.js", "end": [ 1, 26 @@ -123,9 +123,9 @@ "filePaths": [ "function-call.js" ], - "sha1": "3c90d6519f2134b74fb9393f42d42476d101b75a", + "sha1": "038fcd883cc64e100f5886954353987e996ebbcf", "gitDir": "test/corpus/repos/javascript", - "sha2": "92c66af1fe0ad64050da91f4bad6b40fc8690614" + "sha2": "34076873d8c86038c99f24ceb0498b7af38392af" } ,{ "testCaseDescription": "javascript-function-call-replacement-test", @@ -140,7 +140,7 @@ 1, 20 ], - "name": "function-call.js", + "filepath": "function-call.js", "end": [ 1, 26 @@ -151,7 +151,7 @@ 1, 20 ], - "name": "function-call.js", + "filepath": "function-call.js", "end": [ 1, 26 @@ -169,9 +169,9 @@ "filePaths": [ "function-call.js" ], - "sha1": "92c66af1fe0ad64050da91f4bad6b40fc8690614", + "sha1": "34076873d8c86038c99f24ceb0498b7af38392af", "gitDir": "test/corpus/repos/javascript", - "sha2": "23b31eae7b695b2ec4f2bb2e5d66746215dd718e" + "sha2": "17fbdc7f0845828b7692bc764252e2dfe3bb1631" } ,{ "testCaseDescription": "javascript-function-call-delete-replacement-test", @@ -185,7 +185,7 @@ 1, 1 ], - "name": "function-call.js", + "filepath": "function-call.js", "end": [ 1, 27 @@ -202,7 +202,7 @@ 2, 1 ], - "name": "function-call.js", + "filepath": "function-call.js", "end": [ 2, 27 @@ -219,7 +219,7 @@ 2, 1 ], - "name": "function-call.js", + "filepath": "function-call.js", "end": [ 2, 27 @@ -236,9 +236,9 @@ "filePaths": [ "function-call.js" ], - "sha1": "23b31eae7b695b2ec4f2bb2e5d66746215dd718e", + "sha1": "17fbdc7f0845828b7692bc764252e2dfe3bb1631", "gitDir": "test/corpus/repos/javascript", - "sha2": "050239bb60162d04425370eb4efa229b7fb6b8f5" + "sha2": "52cf80147533913c6b3f0a674141d9681d26b121" } ,{ "testCaseDescription": "javascript-function-call-delete-test", @@ -252,7 +252,7 @@ 1, 1 ], - "name": "function-call.js", + "filepath": "function-call.js", "end": [ 1, 27 @@ -269,9 +269,9 @@ "filePaths": [ "function-call.js" ], - "sha1": "050239bb60162d04425370eb4efa229b7fb6b8f5", + "sha1": "52cf80147533913c6b3f0a674141d9681d26b121", "gitDir": "test/corpus/repos/javascript", - "sha2": "14b6c7a0fc4a775c9915ccbf0a9082b5a0566e01" + "sha2": "237338ec6bf7dadc1289bb2f74252fd921347dda" } ,{ "testCaseDescription": "javascript-function-call-delete-rest-test", @@ -285,7 +285,7 @@ 1, 1 ], - "name": "function-call.js", + "filepath": "function-call.js", "end": [ 1, 27 @@ -302,7 +302,7 @@ "filePaths": [ "function-call.js" ], - "sha1": "14b6c7a0fc4a775c9915ccbf0a9082b5a0566e01", + "sha1": "237338ec6bf7dadc1289bb2f74252fd921347dda", "gitDir": "test/corpus/repos/javascript", - "sha2": "1eac526dd11d55220946d9b6306e3031c11e73a7" + "sha2": "fb0210aaf5fee5597a797a052d27aa1428b69f4a" }] diff --git a/test/corpus/diff-summaries/javascript/function.json b/test/corpus/diff-summaries/javascript/function.json index e855ec70e..66220f8e5 100644 --- a/test/corpus/diff-summaries/javascript/function.json +++ b/test/corpus/diff-summaries/javascript/function.json @@ -10,7 +10,7 @@ 1, 1 ], - "name": "function.js", + "filepath": "function.js", "end": [ 1, 31 @@ -27,9 +27,9 @@ "filePaths": [ "function.js" ], - "sha1": "0921c7be9afb30bdf6fa3861d12c20a87ae67736", + "sha1": "f1f90eaec662b19f812bcd5cf97dc4c33579432a", "gitDir": "test/corpus/repos/javascript", - "sha2": "c14206873e94c5b71dcaef2a68cc885f9fe02438" + "sha2": "91b60f943a0bc9c8fdf884a37fbe268812250c26" } ,{ "testCaseDescription": "javascript-function-replacement-insert-test", @@ -43,7 +43,7 @@ 1, 1 ], - "name": "function.js", + "filepath": "function.js", "end": [ 1, 31 @@ -60,7 +60,7 @@ 2, 1 ], - "name": "function.js", + "filepath": "function.js", "end": [ 2, 31 @@ -77,9 +77,9 @@ "filePaths": [ "function.js" ], - "sha1": "c14206873e94c5b71dcaef2a68cc885f9fe02438", + "sha1": "91b60f943a0bc9c8fdf884a37fbe268812250c26", "gitDir": "test/corpus/repos/javascript", - "sha2": "be57190fb1f51d913dfeb73c34d00dc57fcb1872" + "sha2": "cc6480c842fd35a365c64983b9bb436c703b1b23" } ,{ "testCaseDescription": "javascript-function-delete-insert-test", @@ -94,7 +94,7 @@ 1, 24 ], - "name": "function.js", + "filepath": "function.js", "end": [ 1, 28 @@ -105,7 +105,7 @@ 1, 24 ], - "name": "function.js", + "filepath": "function.js", "end": [ 1, 28 @@ -123,9 +123,9 @@ "filePaths": [ "function.js" ], - "sha1": "be57190fb1f51d913dfeb73c34d00dc57fcb1872", + "sha1": "cc6480c842fd35a365c64983b9bb436c703b1b23", "gitDir": "test/corpus/repos/javascript", - "sha2": "fbadfc3fbbde8967568595bb4675ddc476126daf" + "sha2": "41b45e9c0db1380e4b33811ab79708173546579a" } ,{ "testCaseDescription": "javascript-function-replacement-test", @@ -140,7 +140,7 @@ 1, 24 ], - "name": "function.js", + "filepath": "function.js", "end": [ 1, 28 @@ -151,7 +151,7 @@ 1, 24 ], - "name": "function.js", + "filepath": "function.js", "end": [ 1, 28 @@ -169,9 +169,9 @@ "filePaths": [ "function.js" ], - "sha1": "fbadfc3fbbde8967568595bb4675ddc476126daf", + "sha1": "41b45e9c0db1380e4b33811ab79708173546579a", "gitDir": "test/corpus/repos/javascript", - "sha2": "57f9bf7c0a45a4f94d567465b6b977343d32f50b" + "sha2": "b474469be8c7d7f823438fbe7ad01b07859378c7" } ,{ "testCaseDescription": "javascript-function-delete-replacement-test", @@ -185,7 +185,7 @@ 1, 1 ], - "name": "function.js", + "filepath": "function.js", "end": [ 1, 31 @@ -202,7 +202,7 @@ 2, 1 ], - "name": "function.js", + "filepath": "function.js", "end": [ 2, 31 @@ -219,7 +219,7 @@ 2, 1 ], - "name": "function.js", + "filepath": "function.js", "end": [ 2, 31 @@ -236,9 +236,9 @@ "filePaths": [ "function.js" ], - "sha1": "57f9bf7c0a45a4f94d567465b6b977343d32f50b", + "sha1": "b474469be8c7d7f823438fbe7ad01b07859378c7", "gitDir": "test/corpus/repos/javascript", - "sha2": "d35302be0f16f464cc4d0097a751e65d00abc9a1" + "sha2": "651fe75158ddd05cf54b949988612ec1251dae2e" } ,{ "testCaseDescription": "javascript-function-delete-test", @@ -252,7 +252,7 @@ 1, 1 ], - "name": "function.js", + "filepath": "function.js", "end": [ 1, 31 @@ -269,9 +269,9 @@ "filePaths": [ "function.js" ], - "sha1": "d35302be0f16f464cc4d0097a751e65d00abc9a1", + "sha1": "651fe75158ddd05cf54b949988612ec1251dae2e", "gitDir": "test/corpus/repos/javascript", - "sha2": "0e0a3468af5fc91169f996a1334b146594d1e795" + "sha2": "366ae8f7b8fe47ca50de197b15c60bb565806a97" } ,{ "testCaseDescription": "javascript-function-delete-rest-test", @@ -285,7 +285,7 @@ 1, 1 ], - "name": "function.js", + "filepath": "function.js", "end": [ 1, 31 @@ -302,7 +302,7 @@ "filePaths": [ "function.js" ], - "sha1": "0e0a3468af5fc91169f996a1334b146594d1e795", + "sha1": "366ae8f7b8fe47ca50de197b15c60bb565806a97", "gitDir": "test/corpus/repos/javascript", - "sha2": "2327a0433e3123ddf19226ee5172c928f24b3af1" + "sha2": "a495563711f9bcf2719eea2cf654af90e7ce2202" }] diff --git a/test/corpus/diff-summaries/javascript/generator-function.json b/test/corpus/diff-summaries/javascript/generator-function.json index 63cf0b746..d511879c5 100644 --- a/test/corpus/diff-summaries/javascript/generator-function.json +++ b/test/corpus/diff-summaries/javascript/generator-function.json @@ -10,7 +10,7 @@ 1, 1 ], - "name": "generator-function.js", + "filepath": "generator-function.js", "end": [ 1, 59 @@ -27,9 +27,9 @@ "filePaths": [ "generator-function.js" ], - "sha1": "dcaa57653ecd13d885de551a47032d37ef10e47e", + "sha1": "149f58afa30a9e7980256083722f2946eefb47c4", "gitDir": "test/corpus/repos/javascript", - "sha2": "69b059e9e82e91d554c61235b348c86fc8848d37" + "sha2": "ffa54adc9b9632ff252008e3c67868b2966722a0" } ,{ "testCaseDescription": "javascript-generator-function-replacement-insert-test", @@ -43,7 +43,7 @@ 1, 1 ], - "name": "generator-function.js", + "filepath": "generator-function.js", "end": [ 1, 62 @@ -60,7 +60,7 @@ 2, 1 ], - "name": "generator-function.js", + "filepath": "generator-function.js", "end": [ 2, 59 @@ -77,9 +77,9 @@ "filePaths": [ "generator-function.js" ], - "sha1": "69b059e9e82e91d554c61235b348c86fc8848d37", + "sha1": "ffa54adc9b9632ff252008e3c67868b2966722a0", "gitDir": "test/corpus/repos/javascript", - "sha2": "8fc9682cd35f3ba8d4fd15f05651d0a917e755e8" + "sha2": "ee493591637ea4d63d8725e48e367787d1b6ec38" } ,{ "testCaseDescription": "javascript-generator-function-delete-insert-test", @@ -94,7 +94,7 @@ 1, 11 ], - "name": "generator-function.js", + "filepath": "generator-function.js", "end": [ 1, 27 @@ -105,7 +105,7 @@ 1, 11 ], - "name": "generator-function.js", + "filepath": "generator-function.js", "end": [ 1, 24 @@ -123,9 +123,9 @@ "filePaths": [ "generator-function.js" ], - "sha1": "8fc9682cd35f3ba8d4fd15f05651d0a917e755e8", + "sha1": "ee493591637ea4d63d8725e48e367787d1b6ec38", "gitDir": "test/corpus/repos/javascript", - "sha2": "25bc36bf665a0aff1a83ab961fe4611121a16e2e" + "sha2": "8fbc78c6b70275d3a75bb3510a48b52f792c9076" } ,{ "testCaseDescription": "javascript-generator-function-replacement-test", @@ -140,7 +140,7 @@ 1, 11 ], - "name": "generator-function.js", + "filepath": "generator-function.js", "end": [ 1, 24 @@ -151,7 +151,7 @@ 1, 11 ], - "name": "generator-function.js", + "filepath": "generator-function.js", "end": [ 1, 27 @@ -169,9 +169,9 @@ "filePaths": [ "generator-function.js" ], - "sha1": "25bc36bf665a0aff1a83ab961fe4611121a16e2e", + "sha1": "8fbc78c6b70275d3a75bb3510a48b52f792c9076", "gitDir": "test/corpus/repos/javascript", - "sha2": "1502425cb39a05b219e064e5e5b39a9be6beb18e" + "sha2": "fb7ce24ab32b63a69fde5247b2c5dab460c69d3a" } ,{ "testCaseDescription": "javascript-generator-function-delete-replacement-test", @@ -185,7 +185,7 @@ 1, 1 ], - "name": "generator-function.js", + "filepath": "generator-function.js", "end": [ 1, 62 @@ -202,7 +202,7 @@ 2, 1 ], - "name": "generator-function.js", + "filepath": "generator-function.js", "end": [ 2, 59 @@ -219,7 +219,7 @@ 2, 1 ], - "name": "generator-function.js", + "filepath": "generator-function.js", "end": [ 2, 62 @@ -236,9 +236,9 @@ "filePaths": [ "generator-function.js" ], - "sha1": "1502425cb39a05b219e064e5e5b39a9be6beb18e", + "sha1": "fb7ce24ab32b63a69fde5247b2c5dab460c69d3a", "gitDir": "test/corpus/repos/javascript", - "sha2": "0d9d44b51dbb7c8bd0a0e451bf1fb2a8540d8add" + "sha2": "99cb8f43918c9889a91422aed9b7c259a5e9fef0" } ,{ "testCaseDescription": "javascript-generator-function-delete-test", @@ -252,7 +252,7 @@ 1, 1 ], - "name": "generator-function.js", + "filepath": "generator-function.js", "end": [ 1, 59 @@ -269,9 +269,9 @@ "filePaths": [ "generator-function.js" ], - "sha1": "0d9d44b51dbb7c8bd0a0e451bf1fb2a8540d8add", + "sha1": "99cb8f43918c9889a91422aed9b7c259a5e9fef0", "gitDir": "test/corpus/repos/javascript", - "sha2": "4d4d00350fd9e0ccfc94de3844bd3fee97b7de58" + "sha2": "5789fc0ea2d29bcf72b36380eb926854698a59bd" } ,{ "testCaseDescription": "javascript-generator-function-delete-rest-test", @@ -285,7 +285,7 @@ 1, 1 ], - "name": "generator-function.js", + "filepath": "generator-function.js", "end": [ 1, 62 @@ -302,7 +302,7 @@ "filePaths": [ "generator-function.js" ], - "sha1": "4d4d00350fd9e0ccfc94de3844bd3fee97b7de58", + "sha1": "5789fc0ea2d29bcf72b36380eb926854698a59bd", "gitDir": "test/corpus/repos/javascript", - "sha2": "2757c3a3cfdea7d078af6cd6c05b4355fff8b112" + "sha2": "c5dc96e3f8085902d825448ed51dda2cacd42f2a" }] diff --git a/test/corpus/diff-summaries/javascript/identifier.json b/test/corpus/diff-summaries/javascript/identifier.json index 18fff2a97..980af292c 100644 --- a/test/corpus/diff-summaries/javascript/identifier.json +++ b/test/corpus/diff-summaries/javascript/identifier.json @@ -10,7 +10,7 @@ 1, 1 ], - "name": "identifier.js", + "filepath": "identifier.js", "end": [ 1, 7 @@ -27,9 +27,9 @@ "filePaths": [ "identifier.js" ], - "sha1": "ea0156c09a6d9c183d037bddda50ce815c00548f", + "sha1": "956302f9106f0a7726a0243dc14cdd755693f058", "gitDir": "test/corpus/repos/javascript", - "sha2": "e9c20e9a3247f9c4301b51c97c0e9ebe1d4d34be" + "sha2": "74e3454b97f8a2e99e46d202119c5d3a60cc05e9" } ,{ "testCaseDescription": "javascript-identifier-replacement-insert-test", @@ -43,7 +43,7 @@ 1, 1 ], - "name": "identifier.js", + "filepath": "identifier.js", "end": [ 1, 8 @@ -60,7 +60,7 @@ 2, 1 ], - "name": "identifier.js", + "filepath": "identifier.js", "end": [ 2, 7 @@ -77,9 +77,9 @@ "filePaths": [ "identifier.js" ], - "sha1": "e9c20e9a3247f9c4301b51c97c0e9ebe1d4d34be", + "sha1": "74e3454b97f8a2e99e46d202119c5d3a60cc05e9", "gitDir": "test/corpus/repos/javascript", - "sha2": "bd8e182b45f051c7314f54de7f22423d36767b0a" + "sha2": "d0d4136ff2b94788125eb97a0b3db61cb1faebb0" } ,{ "testCaseDescription": "javascript-identifier-delete-insert-test", @@ -94,7 +94,7 @@ 1, 1 ], - "name": "identifier.js", + "filepath": "identifier.js", "end": [ 1, 8 @@ -105,7 +105,7 @@ 1, 1 ], - "name": "identifier.js", + "filepath": "identifier.js", "end": [ 1, 7 @@ -123,9 +123,9 @@ "filePaths": [ "identifier.js" ], - "sha1": "bd8e182b45f051c7314f54de7f22423d36767b0a", + "sha1": "d0d4136ff2b94788125eb97a0b3db61cb1faebb0", "gitDir": "test/corpus/repos/javascript", - "sha2": "03d5aee6333ae73bb1c9cfc6671d5520601ef290" + "sha2": "370594f8d85a03abb5775575b632368cd6c56e78" } ,{ "testCaseDescription": "javascript-identifier-replacement-test", @@ -140,7 +140,7 @@ 1, 1 ], - "name": "identifier.js", + "filepath": "identifier.js", "end": [ 1, 7 @@ -151,7 +151,7 @@ 1, 1 ], - "name": "identifier.js", + "filepath": "identifier.js", "end": [ 1, 8 @@ -169,9 +169,9 @@ "filePaths": [ "identifier.js" ], - "sha1": "03d5aee6333ae73bb1c9cfc6671d5520601ef290", + "sha1": "370594f8d85a03abb5775575b632368cd6c56e78", "gitDir": "test/corpus/repos/javascript", - "sha2": "ddfc882641f80549771567151156aa80b4a6d443" + "sha2": "9aea17f37b761c953514645cfe3146aaa0f23e73" } ,{ "testCaseDescription": "javascript-identifier-delete-replacement-test", @@ -185,7 +185,7 @@ 1, 1 ], - "name": "identifier.js", + "filepath": "identifier.js", "end": [ 1, 8 @@ -202,7 +202,7 @@ 2, 1 ], - "name": "identifier.js", + "filepath": "identifier.js", "end": [ 2, 7 @@ -219,7 +219,7 @@ 2, 1 ], - "name": "identifier.js", + "filepath": "identifier.js", "end": [ 2, 8 @@ -236,9 +236,9 @@ "filePaths": [ "identifier.js" ], - "sha1": "ddfc882641f80549771567151156aa80b4a6d443", + "sha1": "9aea17f37b761c953514645cfe3146aaa0f23e73", "gitDir": "test/corpus/repos/javascript", - "sha2": "9a8d227c90fea676142f53a5d98aa4fe54ea15f2" + "sha2": "a7c4bf3f2ddf6abeba6d2d35522951332f7d75a3" } ,{ "testCaseDescription": "javascript-identifier-delete-test", @@ -252,7 +252,7 @@ 1, 1 ], - "name": "identifier.js", + "filepath": "identifier.js", "end": [ 1, 7 @@ -269,9 +269,9 @@ "filePaths": [ "identifier.js" ], - "sha1": "9a8d227c90fea676142f53a5d98aa4fe54ea15f2", + "sha1": "a7c4bf3f2ddf6abeba6d2d35522951332f7d75a3", "gitDir": "test/corpus/repos/javascript", - "sha2": "154521e82253448dfe113e5bd2fdb8f5d72fc002" + "sha2": "ff61471368a9273f8f5eb3823ad210b53576e36c" } ,{ "testCaseDescription": "javascript-identifier-delete-rest-test", @@ -285,7 +285,7 @@ 1, 1 ], - "name": "identifier.js", + "filepath": "identifier.js", "end": [ 1, 8 @@ -302,7 +302,7 @@ "filePaths": [ "identifier.js" ], - "sha1": "154521e82253448dfe113e5bd2fdb8f5d72fc002", + "sha1": "ff61471368a9273f8f5eb3823ad210b53576e36c", "gitDir": "test/corpus/repos/javascript", - "sha2": "562fd7786138fba4253581a1f2995c02007f74b9" + "sha2": "29afb7ea7664c9b87e9a1f80cee7d64db934ba84" }] diff --git a/test/corpus/diff-summaries/javascript/if-else.json b/test/corpus/diff-summaries/javascript/if-else.json index d314e7c11..b53db332a 100644 --- a/test/corpus/diff-summaries/javascript/if-else.json +++ b/test/corpus/diff-summaries/javascript/if-else.json @@ -10,7 +10,7 @@ 1, 1 ], - "name": "if-else.js", + "filepath": "if-else.js", "end": [ 1, 25 @@ -27,9 +27,9 @@ "filePaths": [ "if-else.js" ], - "sha1": "c9021762fc3f372be0d71362df586edc1e74f4d0", + "sha1": "b5de1a134ae3231ac21b6b01c4f56ea72236bde6", "gitDir": "test/corpus/repos/javascript", - "sha2": "4670ff79891fe66aef3f92c207b6b93a6b13dd20" + "sha2": "72eee07d9bc53d5e852509904c5cb5ca17861f15" } ,{ "testCaseDescription": "javascript-if-else-replacement-insert-test", @@ -43,7 +43,7 @@ 1, 1 ], - "name": "if-else.js", + "filepath": "if-else.js", "end": [ 1, 29 @@ -60,7 +60,7 @@ 2, 1 ], - "name": "if-else.js", + "filepath": "if-else.js", "end": [ 2, 25 @@ -77,9 +77,9 @@ "filePaths": [ "if-else.js" ], - "sha1": "4670ff79891fe66aef3f92c207b6b93a6b13dd20", + "sha1": "72eee07d9bc53d5e852509904c5cb5ca17861f15", "gitDir": "test/corpus/repos/javascript", - "sha2": "e47e54e15d63f3d9b67d2fe4bfd9e9d9b98f83de" + "sha2": "92ac5f21e46618d8000692d5908caef81bf793ac" } ,{ "testCaseDescription": "javascript-if-else-delete-insert-test", @@ -94,7 +94,7 @@ 1, 1 ], - "name": "if-else.js", + "filepath": "if-else.js", "end": [ 1, 29 @@ -105,7 +105,7 @@ 1, 1 ], - "name": "if-else.js", + "filepath": "if-else.js", "end": [ 1, 25 @@ -123,9 +123,9 @@ "filePaths": [ "if-else.js" ], - "sha1": "e47e54e15d63f3d9b67d2fe4bfd9e9d9b98f83de", + "sha1": "92ac5f21e46618d8000692d5908caef81bf793ac", "gitDir": "test/corpus/repos/javascript", - "sha2": "ff71eaad0cda4ae6e40a1ace67c8e8855129f297" + "sha2": "26b5fe7a6181aa76479a875f7c2c25af3e15b1b7" } ,{ "testCaseDescription": "javascript-if-else-replacement-test", @@ -140,7 +140,7 @@ 1, 1 ], - "name": "if-else.js", + "filepath": "if-else.js", "end": [ 1, 25 @@ -151,7 +151,7 @@ 1, 1 ], - "name": "if-else.js", + "filepath": "if-else.js", "end": [ 1, 29 @@ -169,9 +169,9 @@ "filePaths": [ "if-else.js" ], - "sha1": "ff71eaad0cda4ae6e40a1ace67c8e8855129f297", + "sha1": "26b5fe7a6181aa76479a875f7c2c25af3e15b1b7", "gitDir": "test/corpus/repos/javascript", - "sha2": "f73d3a5494c68a92758265e047ce766571786700" + "sha2": "d0584df7c3083752130b889896f70c608cae92a8" } ,{ "testCaseDescription": "javascript-if-else-delete-replacement-test", @@ -185,7 +185,7 @@ 1, 1 ], - "name": "if-else.js", + "filepath": "if-else.js", "end": [ 1, 29 @@ -202,7 +202,7 @@ 2, 1 ], - "name": "if-else.js", + "filepath": "if-else.js", "end": [ 2, 25 @@ -219,7 +219,7 @@ 2, 1 ], - "name": "if-else.js", + "filepath": "if-else.js", "end": [ 2, 29 @@ -236,9 +236,9 @@ "filePaths": [ "if-else.js" ], - "sha1": "f73d3a5494c68a92758265e047ce766571786700", + "sha1": "d0584df7c3083752130b889896f70c608cae92a8", "gitDir": "test/corpus/repos/javascript", - "sha2": "5e1fd2dc43887977b5ca0c6fce1e12fcbdc46882" + "sha2": "ae7cc92656f03d10bf29c8e46dfc2eb9fc0a0172" } ,{ "testCaseDescription": "javascript-if-else-delete-test", @@ -252,7 +252,7 @@ 1, 1 ], - "name": "if-else.js", + "filepath": "if-else.js", "end": [ 1, 25 @@ -269,9 +269,9 @@ "filePaths": [ "if-else.js" ], - "sha1": "5e1fd2dc43887977b5ca0c6fce1e12fcbdc46882", + "sha1": "ae7cc92656f03d10bf29c8e46dfc2eb9fc0a0172", "gitDir": "test/corpus/repos/javascript", - "sha2": "249e0e5a68af8672af85b0a064593d5840ef11c7" + "sha2": "50ca41028aceb89fd8d339ea7957b51cf440a7ab" } ,{ "testCaseDescription": "javascript-if-else-delete-rest-test", @@ -285,7 +285,7 @@ 1, 1 ], - "name": "if-else.js", + "filepath": "if-else.js", "end": [ 1, 29 @@ -302,7 +302,7 @@ "filePaths": [ "if-else.js" ], - "sha1": "249e0e5a68af8672af85b0a064593d5840ef11c7", + "sha1": "50ca41028aceb89fd8d339ea7957b51cf440a7ab", "gitDir": "test/corpus/repos/javascript", - "sha2": "b2046cbd2baf7870677913d1acc35696f7a97f84" + "sha2": "24e0108747de5b5607cb53209256451ba88a5b34" }] diff --git a/test/corpus/diff-summaries/javascript/if.json b/test/corpus/diff-summaries/javascript/if.json index ed450b2d0..ded3095a8 100644 --- a/test/corpus/diff-summaries/javascript/if.json +++ b/test/corpus/diff-summaries/javascript/if.json @@ -10,7 +10,7 @@ 1, 1 ], - "name": "if.js", + "filepath": "if.js", "end": [ 1, 19 @@ -27,9 +27,9 @@ "filePaths": [ "if.js" ], - "sha1": "88eddedb2d7666ebcc74cb1693e7f24e13e4e481", + "sha1": "c0d6ae2924b71cacb33bd7d1b453089152e5ecb8", "gitDir": "test/corpus/repos/javascript", - "sha2": "398030c49850abab6e773e4222952743bbd35619" + "sha2": "c0b1419a82de077ea1eebfda3182a4a390ee35c9" } ,{ "testCaseDescription": "javascript-if-replacement-insert-test", @@ -43,7 +43,7 @@ 1, 1 ], - "name": "if.js", + "filepath": "if.js", "end": [ 1, 24 @@ -60,7 +60,7 @@ 2, 1 ], - "name": "if.js", + "filepath": "if.js", "end": [ 2, 19 @@ -77,9 +77,9 @@ "filePaths": [ "if.js" ], - "sha1": "398030c49850abab6e773e4222952743bbd35619", + "sha1": "c0b1419a82de077ea1eebfda3182a4a390ee35c9", "gitDir": "test/corpus/repos/javascript", - "sha2": "a5b0e3a01683c3273038baed42d8cb553f076528" + "sha2": "d540f86a390307f222dd387865f8a983031b58f5" } ,{ "testCaseDescription": "javascript-if-delete-insert-test", @@ -94,7 +94,7 @@ 1, 1 ], - "name": "if.js", + "filepath": "if.js", "end": [ 1, 24 @@ -105,7 +105,7 @@ 1, 1 ], - "name": "if.js", + "filepath": "if.js", "end": [ 1, 19 @@ -123,9 +123,9 @@ "filePaths": [ "if.js" ], - "sha1": "a5b0e3a01683c3273038baed42d8cb553f076528", + "sha1": "d540f86a390307f222dd387865f8a983031b58f5", "gitDir": "test/corpus/repos/javascript", - "sha2": "f6e410f5c881a7706564be66e6e0c346b1c83319" + "sha2": "dc24f13daf6aed55de58817b6980a1bdb3feba94" } ,{ "testCaseDescription": "javascript-if-replacement-test", @@ -140,7 +140,7 @@ 1, 1 ], - "name": "if.js", + "filepath": "if.js", "end": [ 1, 19 @@ -151,7 +151,7 @@ 1, 1 ], - "name": "if.js", + "filepath": "if.js", "end": [ 1, 24 @@ -169,9 +169,9 @@ "filePaths": [ "if.js" ], - "sha1": "f6e410f5c881a7706564be66e6e0c346b1c83319", + "sha1": "dc24f13daf6aed55de58817b6980a1bdb3feba94", "gitDir": "test/corpus/repos/javascript", - "sha2": "e4e027e6a7c794c693011b35ef5e7d7e0129d4d2" + "sha2": "e0c31f28e9fe40aefacbfd928d359d3b00217fa7" } ,{ "testCaseDescription": "javascript-if-delete-replacement-test", @@ -185,7 +185,7 @@ 1, 1 ], - "name": "if.js", + "filepath": "if.js", "end": [ 1, 24 @@ -202,7 +202,7 @@ 2, 1 ], - "name": "if.js", + "filepath": "if.js", "end": [ 2, 19 @@ -219,7 +219,7 @@ 2, 1 ], - "name": "if.js", + "filepath": "if.js", "end": [ 2, 24 @@ -236,9 +236,9 @@ "filePaths": [ "if.js" ], - "sha1": "e4e027e6a7c794c693011b35ef5e7d7e0129d4d2", + "sha1": "e0c31f28e9fe40aefacbfd928d359d3b00217fa7", "gitDir": "test/corpus/repos/javascript", - "sha2": "d74f4b903c9888429dd3d8d8d604bac231caa3f2" + "sha2": "17f14120236233af322a9b79fbbe0dd72550425d" } ,{ "testCaseDescription": "javascript-if-delete-test", @@ -252,7 +252,7 @@ 1, 1 ], - "name": "if.js", + "filepath": "if.js", "end": [ 1, 19 @@ -269,9 +269,9 @@ "filePaths": [ "if.js" ], - "sha1": "d74f4b903c9888429dd3d8d8d604bac231caa3f2", + "sha1": "17f14120236233af322a9b79fbbe0dd72550425d", "gitDir": "test/corpus/repos/javascript", - "sha2": "37d76cba66fa561e813c9c7b38b8e3b0edf0be20" + "sha2": "facfb7197d55103e3cb9ba0e0b32fd5c5605878b" } ,{ "testCaseDescription": "javascript-if-delete-rest-test", @@ -285,7 +285,7 @@ 1, 1 ], - "name": "if.js", + "filepath": "if.js", "end": [ 1, 24 @@ -302,7 +302,7 @@ "filePaths": [ "if.js" ], - "sha1": "37d76cba66fa561e813c9c7b38b8e3b0edf0be20", + "sha1": "facfb7197d55103e3cb9ba0e0b32fd5c5605878b", "gitDir": "test/corpus/repos/javascript", - "sha2": "c9021762fc3f372be0d71362df586edc1e74f4d0" + "sha2": "9d2df250626ca6e689d2c7c821579412e6ba99d6" }] diff --git a/test/corpus/diff-summaries/javascript/math-assignment-operator.json b/test/corpus/diff-summaries/javascript/math-assignment-operator.json index c85ce3a0d..c466d7a04 100644 --- a/test/corpus/diff-summaries/javascript/math-assignment-operator.json +++ b/test/corpus/diff-summaries/javascript/math-assignment-operator.json @@ -10,7 +10,7 @@ 1, 1 ], - "name": "math-assignment-operator.js", + "filepath": "math-assignment-operator.js", "end": [ 1, 7 @@ -27,9 +27,9 @@ "filePaths": [ "math-assignment-operator.js" ], - "sha1": "5fc82ac3374f4c8d50af76e2ae299a59e4cff396", + "sha1": "36746b2d6ba87364134adab0f0a1b24c9206dc15", "gitDir": "test/corpus/repos/javascript", - "sha2": "c1179440cd79faa8f00d6b50c8f99b6f4fa3b2c7" + "sha2": "926f27398fb4f6b893d7aef6c25aaa73b5febd43" } ,{ "testCaseDescription": "javascript-math-assignment-operator-replacement-insert-test", @@ -43,7 +43,7 @@ 1, 1 ], - "name": "math-assignment-operator.js", + "filepath": "math-assignment-operator.js", "end": [ 1, 7 @@ -60,7 +60,7 @@ 2, 1 ], - "name": "math-assignment-operator.js", + "filepath": "math-assignment-operator.js", "end": [ 2, 7 @@ -77,9 +77,9 @@ "filePaths": [ "math-assignment-operator.js" ], - "sha1": "c1179440cd79faa8f00d6b50c8f99b6f4fa3b2c7", + "sha1": "926f27398fb4f6b893d7aef6c25aaa73b5febd43", "gitDir": "test/corpus/repos/javascript", - "sha2": "9f90dacee15220d6d61f1d9d221980c7c793c7a3" + "sha2": "9c14747b6048fd754a38cb03e590c14e78c251b0" } ,{ "testCaseDescription": "javascript-math-assignment-operator-delete-insert-test", @@ -94,7 +94,7 @@ 1, 6 ], - "name": "math-assignment-operator.js", + "filepath": "math-assignment-operator.js", "end": [ 1, 7 @@ -105,7 +105,7 @@ 1, 6 ], - "name": "math-assignment-operator.js", + "filepath": "math-assignment-operator.js", "end": [ 1, 7 @@ -123,9 +123,9 @@ "filePaths": [ "math-assignment-operator.js" ], - "sha1": "9f90dacee15220d6d61f1d9d221980c7c793c7a3", + "sha1": "9c14747b6048fd754a38cb03e590c14e78c251b0", "gitDir": "test/corpus/repos/javascript", - "sha2": "390eb2aa1f63abbaae7f33139e1db4ec60ddb736" + "sha2": "532ffbd748f6e6c091a00b830ddc7f4a1f0db7d9" } ,{ "testCaseDescription": "javascript-math-assignment-operator-replacement-test", @@ -140,7 +140,7 @@ 1, 6 ], - "name": "math-assignment-operator.js", + "filepath": "math-assignment-operator.js", "end": [ 1, 7 @@ -151,7 +151,7 @@ 1, 6 ], - "name": "math-assignment-operator.js", + "filepath": "math-assignment-operator.js", "end": [ 1, 7 @@ -169,9 +169,9 @@ "filePaths": [ "math-assignment-operator.js" ], - "sha1": "390eb2aa1f63abbaae7f33139e1db4ec60ddb736", + "sha1": "532ffbd748f6e6c091a00b830ddc7f4a1f0db7d9", "gitDir": "test/corpus/repos/javascript", - "sha2": "7b6eff26944c44962cecfb8b041a006fc4d5cff4" + "sha2": "545504f9b2a6e43637c7ca9d177b1195cb01261f" } ,{ "testCaseDescription": "javascript-math-assignment-operator-delete-replacement-test", @@ -185,7 +185,7 @@ 1, 1 ], - "name": "math-assignment-operator.js", + "filepath": "math-assignment-operator.js", "end": [ 1, 7 @@ -202,7 +202,7 @@ 2, 1 ], - "name": "math-assignment-operator.js", + "filepath": "math-assignment-operator.js", "end": [ 2, 7 @@ -219,7 +219,7 @@ 2, 1 ], - "name": "math-assignment-operator.js", + "filepath": "math-assignment-operator.js", "end": [ 2, 7 @@ -236,9 +236,9 @@ "filePaths": [ "math-assignment-operator.js" ], - "sha1": "7b6eff26944c44962cecfb8b041a006fc4d5cff4", + "sha1": "545504f9b2a6e43637c7ca9d177b1195cb01261f", "gitDir": "test/corpus/repos/javascript", - "sha2": "35b4ffd0eeafbae6113ad22b86a1d278f5ed26a8" + "sha2": "7208427c499ba69f5888725545278be2106db3d5" } ,{ "testCaseDescription": "javascript-math-assignment-operator-delete-test", @@ -252,7 +252,7 @@ 1, 1 ], - "name": "math-assignment-operator.js", + "filepath": "math-assignment-operator.js", "end": [ 1, 7 @@ -269,9 +269,9 @@ "filePaths": [ "math-assignment-operator.js" ], - "sha1": "35b4ffd0eeafbae6113ad22b86a1d278f5ed26a8", + "sha1": "7208427c499ba69f5888725545278be2106db3d5", "gitDir": "test/corpus/repos/javascript", - "sha2": "411c2e22bb0eccdeb3d32fdc588e9e1a92ac4442" + "sha2": "0ad9f6da8726302d846eec6f97575074d13ab5a6" } ,{ "testCaseDescription": "javascript-math-assignment-operator-delete-rest-test", @@ -285,7 +285,7 @@ 1, 1 ], - "name": "math-assignment-operator.js", + "filepath": "math-assignment-operator.js", "end": [ 1, 7 @@ -302,7 +302,7 @@ "filePaths": [ "math-assignment-operator.js" ], - "sha1": "411c2e22bb0eccdeb3d32fdc588e9e1a92ac4442", + "sha1": "0ad9f6da8726302d846eec6f97575074d13ab5a6", "gitDir": "test/corpus/repos/javascript", - "sha2": "b0363eb07d0284130aab04183573dcd31fa7f221" + "sha2": "04b4cf44ac56798ef4a911f2e996686abbb4ab8d" }] diff --git a/test/corpus/diff-summaries/javascript/math-operator.json b/test/corpus/diff-summaries/javascript/math-operator.json index dc0dbcc01..bfbf6537a 100644 --- a/test/corpus/diff-summaries/javascript/math-operator.json +++ b/test/corpus/diff-summaries/javascript/math-operator.json @@ -10,7 +10,7 @@ 1, 1 ], - "name": "math-operator.js", + "filepath": "math-operator.js", "end": [ 1, 18 @@ -27,9 +27,9 @@ "filePaths": [ "math-operator.js" ], - "sha1": "952d18ccd1d4413a1252458befbb6593253aa794", + "sha1": "b3c83533a75769c4c1381c9ff0ac6600f525c9c3", "gitDir": "test/corpus/repos/javascript", - "sha2": "0f5f7cf116643cca9937c190200836a873710883" + "sha2": "9bba3bf5ddfcae9cad9d4cc6e1e820cdf4a38d86" } ,{ "testCaseDescription": "javascript-math-operator-replacement-insert-test", @@ -43,7 +43,7 @@ 1, 1 ], - "name": "math-operator.js", + "filepath": "math-operator.js", "end": [ 1, 18 @@ -60,7 +60,7 @@ 2, 1 ], - "name": "math-operator.js", + "filepath": "math-operator.js", "end": [ 2, 18 @@ -77,9 +77,9 @@ "filePaths": [ "math-operator.js" ], - "sha1": "0f5f7cf116643cca9937c190200836a873710883", + "sha1": "9bba3bf5ddfcae9cad9d4cc6e1e820cdf4a38d86", "gitDir": "test/corpus/repos/javascript", - "sha2": "1da37893a9e9441662973874ed47dd77654338fb" + "sha2": "2f8acf49d3eb7880a853354235179426fb10419d" } ,{ "testCaseDescription": "javascript-math-operator-delete-insert-test", @@ -94,7 +94,7 @@ 1, 9 ], - "name": "math-operator.js", + "filepath": "math-operator.js", "end": [ 1, 10 @@ -105,7 +105,7 @@ 1, 9 ], - "name": "math-operator.js", + "filepath": "math-operator.js", "end": [ 1, 10 @@ -124,7 +124,7 @@ 1, 17 ], - "name": "math-operator.js", + "filepath": "math-operator.js", "end": [ 1, 18 @@ -135,7 +135,7 @@ 1, 17 ], - "name": "math-operator.js", + "filepath": "math-operator.js", "end": [ 1, 18 @@ -153,9 +153,9 @@ "filePaths": [ "math-operator.js" ], - "sha1": "1da37893a9e9441662973874ed47dd77654338fb", + "sha1": "2f8acf49d3eb7880a853354235179426fb10419d", "gitDir": "test/corpus/repos/javascript", - "sha2": "aac275442430a4112052e502188bdc77cb31dc58" + "sha2": "95e60cde18a627b93d31cefe0db7a9cf76097cdd" } ,{ "testCaseDescription": "javascript-math-operator-replacement-test", @@ -170,7 +170,7 @@ 1, 9 ], - "name": "math-operator.js", + "filepath": "math-operator.js", "end": [ 1, 10 @@ -181,7 +181,7 @@ 1, 9 ], - "name": "math-operator.js", + "filepath": "math-operator.js", "end": [ 1, 10 @@ -200,7 +200,7 @@ 1, 17 ], - "name": "math-operator.js", + "filepath": "math-operator.js", "end": [ 1, 18 @@ -211,7 +211,7 @@ 1, 17 ], - "name": "math-operator.js", + "filepath": "math-operator.js", "end": [ 1, 18 @@ -229,9 +229,9 @@ "filePaths": [ "math-operator.js" ], - "sha1": "aac275442430a4112052e502188bdc77cb31dc58", + "sha1": "95e60cde18a627b93d31cefe0db7a9cf76097cdd", "gitDir": "test/corpus/repos/javascript", - "sha2": "a42e5df3587157b8b86c4613a0460af6ac0d9477" + "sha2": "9cb20ba0bc191365715b6d16c5deffc0a6b1bfc9" } ,{ "testCaseDescription": "javascript-math-operator-delete-replacement-test", @@ -245,7 +245,7 @@ 1, 1 ], - "name": "math-operator.js", + "filepath": "math-operator.js", "end": [ 1, 18 @@ -262,7 +262,7 @@ 2, 1 ], - "name": "math-operator.js", + "filepath": "math-operator.js", "end": [ 2, 18 @@ -279,7 +279,7 @@ 2, 1 ], - "name": "math-operator.js", + "filepath": "math-operator.js", "end": [ 2, 18 @@ -296,9 +296,9 @@ "filePaths": [ "math-operator.js" ], - "sha1": "a42e5df3587157b8b86c4613a0460af6ac0d9477", + "sha1": "9cb20ba0bc191365715b6d16c5deffc0a6b1bfc9", "gitDir": "test/corpus/repos/javascript", - "sha2": "646e506df8f4ace3fda519ad69f21f13f34aa408" + "sha2": "cb9a6cbcbc723642b15197aeca53b95721097596" } ,{ "testCaseDescription": "javascript-math-operator-delete-test", @@ -312,7 +312,7 @@ 1, 1 ], - "name": "math-operator.js", + "filepath": "math-operator.js", "end": [ 1, 18 @@ -329,9 +329,9 @@ "filePaths": [ "math-operator.js" ], - "sha1": "646e506df8f4ace3fda519ad69f21f13f34aa408", + "sha1": "cb9a6cbcbc723642b15197aeca53b95721097596", "gitDir": "test/corpus/repos/javascript", - "sha2": "d261c59941740a794efd74dd3bd3e1b88df1d436" + "sha2": "56333e8f5e6c30f22fc4b324fcdde287f4b75d91" } ,{ "testCaseDescription": "javascript-math-operator-delete-rest-test", @@ -345,7 +345,7 @@ 1, 1 ], - "name": "math-operator.js", + "filepath": "math-operator.js", "end": [ 1, 18 @@ -362,7 +362,7 @@ "filePaths": [ "math-operator.js" ], - "sha1": "d261c59941740a794efd74dd3bd3e1b88df1d436", + "sha1": "56333e8f5e6c30f22fc4b324fcdde287f4b75d91", "gitDir": "test/corpus/repos/javascript", - "sha2": "4a00f98e1f34850ca8d14b8f33de4f8a0fcb7c40" + "sha2": "82e37684278e3bac7d2eb9df508781b1207aa1cd" }] diff --git a/test/corpus/diff-summaries/javascript/member-access-assignment.json b/test/corpus/diff-summaries/javascript/member-access-assignment.json index 60d973914..e6089cded 100644 --- a/test/corpus/diff-summaries/javascript/member-access-assignment.json +++ b/test/corpus/diff-summaries/javascript/member-access-assignment.json @@ -10,7 +10,7 @@ 1, 1 ], - "name": "member-access-assignment.js", + "filepath": "member-access-assignment.js", "end": [ 1, 8 @@ -27,9 +27,9 @@ "filePaths": [ "member-access-assignment.js" ], - "sha1": "a4003ba4e78b0ae460decba084c34b15da1aa05e", + "sha1": "7380de134eeae9874be06c3d411dcbb3fb94d015", "gitDir": "test/corpus/repos/javascript", - "sha2": "16101ac65aa3b3af782eafd2e4c93d307ab12a82" + "sha2": "cd496d7f1d2c90c9727e37015319fb990d405494" } ,{ "testCaseDescription": "javascript-member-access-assignment-replacement-insert-test", @@ -43,7 +43,7 @@ 1, 1 ], - "name": "member-access-assignment.js", + "filepath": "member-access-assignment.js", "end": [ 1, 8 @@ -60,7 +60,7 @@ 2, 1 ], - "name": "member-access-assignment.js", + "filepath": "member-access-assignment.js", "end": [ 2, 8 @@ -77,9 +77,9 @@ "filePaths": [ "member-access-assignment.js" ], - "sha1": "16101ac65aa3b3af782eafd2e4c93d307ab12a82", + "sha1": "cd496d7f1d2c90c9727e37015319fb990d405494", "gitDir": "test/corpus/repos/javascript", - "sha2": "73e1be43e07e507caab17a550b53339b59b9ec70" + "sha2": "bd5fd3eb1fd88229399ce2016e7591193b588f0e" } ,{ "testCaseDescription": "javascript-member-access-assignment-delete-insert-test", @@ -94,7 +94,7 @@ 1, 7 ], - "name": "member-access-assignment.js", + "filepath": "member-access-assignment.js", "end": [ 1, 8 @@ -105,7 +105,7 @@ 1, 7 ], - "name": "member-access-assignment.js", + "filepath": "member-access-assignment.js", "end": [ 1, 8 @@ -123,9 +123,9 @@ "filePaths": [ "member-access-assignment.js" ], - "sha1": "73e1be43e07e507caab17a550b53339b59b9ec70", + "sha1": "bd5fd3eb1fd88229399ce2016e7591193b588f0e", "gitDir": "test/corpus/repos/javascript", - "sha2": "b3ddcbd42f82560f26d7223d64fb0a59b3f1fd6d" + "sha2": "b9539036cd2b06a6326151cc379d8732bef57bd2" } ,{ "testCaseDescription": "javascript-member-access-assignment-replacement-test", @@ -140,7 +140,7 @@ 1, 7 ], - "name": "member-access-assignment.js", + "filepath": "member-access-assignment.js", "end": [ 1, 8 @@ -151,7 +151,7 @@ 1, 7 ], - "name": "member-access-assignment.js", + "filepath": "member-access-assignment.js", "end": [ 1, 8 @@ -169,9 +169,9 @@ "filePaths": [ "member-access-assignment.js" ], - "sha1": "b3ddcbd42f82560f26d7223d64fb0a59b3f1fd6d", + "sha1": "b9539036cd2b06a6326151cc379d8732bef57bd2", "gitDir": "test/corpus/repos/javascript", - "sha2": "e8079105133dae2beea64e95d3b491cd3938d322" + "sha2": "2e89afcef070681df977134e2a312bdcb4b1388b" } ,{ "testCaseDescription": "javascript-member-access-assignment-delete-replacement-test", @@ -185,7 +185,7 @@ 1, 1 ], - "name": "member-access-assignment.js", + "filepath": "member-access-assignment.js", "end": [ 1, 8 @@ -202,7 +202,7 @@ 2, 1 ], - "name": "member-access-assignment.js", + "filepath": "member-access-assignment.js", "end": [ 2, 8 @@ -219,7 +219,7 @@ 2, 1 ], - "name": "member-access-assignment.js", + "filepath": "member-access-assignment.js", "end": [ 2, 8 @@ -236,9 +236,9 @@ "filePaths": [ "member-access-assignment.js" ], - "sha1": "e8079105133dae2beea64e95d3b491cd3938d322", + "sha1": "2e89afcef070681df977134e2a312bdcb4b1388b", "gitDir": "test/corpus/repos/javascript", - "sha2": "0205a7fb38a9a6d5b897e5b0e98c9a45c936e89d" + "sha2": "50b47456bf5b0650ad9d88815dea43e280734815" } ,{ "testCaseDescription": "javascript-member-access-assignment-delete-test", @@ -252,7 +252,7 @@ 1, 1 ], - "name": "member-access-assignment.js", + "filepath": "member-access-assignment.js", "end": [ 1, 8 @@ -269,9 +269,9 @@ "filePaths": [ "member-access-assignment.js" ], - "sha1": "0205a7fb38a9a6d5b897e5b0e98c9a45c936e89d", + "sha1": "50b47456bf5b0650ad9d88815dea43e280734815", "gitDir": "test/corpus/repos/javascript", - "sha2": "6c64da67067e3c0291791a301b469486afed28a2" + "sha2": "c3a2723e98e43d147147f02b98ae5d283a7157f8" } ,{ "testCaseDescription": "javascript-member-access-assignment-delete-rest-test", @@ -285,7 +285,7 @@ 1, 1 ], - "name": "member-access-assignment.js", + "filepath": "member-access-assignment.js", "end": [ 1, 8 @@ -302,7 +302,7 @@ "filePaths": [ "member-access-assignment.js" ], - "sha1": "6c64da67067e3c0291791a301b469486afed28a2", + "sha1": "c3a2723e98e43d147147f02b98ae5d283a7157f8", "gitDir": "test/corpus/repos/javascript", - "sha2": "1e25a73e1015c39932d3a621daa9081a4e46a9ba" + "sha2": "005c70a333fc50afa05734f7e6f660d18d53236b" }] diff --git a/test/corpus/diff-summaries/javascript/member-access.json b/test/corpus/diff-summaries/javascript/member-access.json index 94f8abd02..4261c56ba 100644 --- a/test/corpus/diff-summaries/javascript/member-access.json +++ b/test/corpus/diff-summaries/javascript/member-access.json @@ -10,7 +10,7 @@ 1, 1 ], - "name": "member-access.js", + "filepath": "member-access.js", "end": [ 1, 15 @@ -27,9 +27,9 @@ "filePaths": [ "member-access.js" ], - "sha1": "035ebadb21075a55367b83c380264365799ac421", + "sha1": "809449783f5fc8fe8ceead7879dfa8658d896e49", "gitDir": "test/corpus/repos/javascript", - "sha2": "f627d80f233c895dbe4c55592460fab353e58aab" + "sha2": "4a71937ab4674805e2615bba994dc9d4c7d0359f" } ,{ "testCaseDescription": "javascript-member-access-replacement-insert-test", @@ -43,7 +43,7 @@ 1, 1 ], - "name": "member-access.js", + "filepath": "member-access.js", "end": [ 1, 20 @@ -60,7 +60,7 @@ 2, 1 ], - "name": "member-access.js", + "filepath": "member-access.js", "end": [ 2, 15 @@ -77,9 +77,9 @@ "filePaths": [ "member-access.js" ], - "sha1": "f627d80f233c895dbe4c55592460fab353e58aab", + "sha1": "4a71937ab4674805e2615bba994dc9d4c7d0359f", "gitDir": "test/corpus/repos/javascript", - "sha2": "388603ce6932fd40cfee9bddaf18f3f407cf27a6" + "sha2": "d0cd17917390d2dbe77338314a268c760393033d" } ,{ "testCaseDescription": "javascript-member-access-delete-insert-test", @@ -94,7 +94,7 @@ 1, 3 ], - "name": "member-access.js", + "filepath": "member-access.js", "end": [ 1, 20 @@ -105,7 +105,7 @@ 1, 3 ], - "name": "member-access.js", + "filepath": "member-access.js", "end": [ 1, 15 @@ -123,9 +123,9 @@ "filePaths": [ "member-access.js" ], - "sha1": "388603ce6932fd40cfee9bddaf18f3f407cf27a6", + "sha1": "d0cd17917390d2dbe77338314a268c760393033d", "gitDir": "test/corpus/repos/javascript", - "sha2": "fff56d1bd93eeee668ffeac7a30162fa7f81a91b" + "sha2": "ac770284357a8837916b0fd99a600ea842316c3f" } ,{ "testCaseDescription": "javascript-member-access-replacement-test", @@ -140,7 +140,7 @@ 1, 3 ], - "name": "member-access.js", + "filepath": "member-access.js", "end": [ 1, 15 @@ -151,7 +151,7 @@ 1, 3 ], - "name": "member-access.js", + "filepath": "member-access.js", "end": [ 1, 20 @@ -169,9 +169,9 @@ "filePaths": [ "member-access.js" ], - "sha1": "fff56d1bd93eeee668ffeac7a30162fa7f81a91b", + "sha1": "ac770284357a8837916b0fd99a600ea842316c3f", "gitDir": "test/corpus/repos/javascript", - "sha2": "6318121ceeab8d6e2f209d2eaa8476f5c416ebeb" + "sha2": "29c4345d54f21491b5f7500da823d4753a03ab22" } ,{ "testCaseDescription": "javascript-member-access-delete-replacement-test", @@ -185,7 +185,7 @@ 1, 1 ], - "name": "member-access.js", + "filepath": "member-access.js", "end": [ 1, 20 @@ -202,7 +202,7 @@ 2, 1 ], - "name": "member-access.js", + "filepath": "member-access.js", "end": [ 2, 15 @@ -219,7 +219,7 @@ 2, 1 ], - "name": "member-access.js", + "filepath": "member-access.js", "end": [ 2, 20 @@ -236,9 +236,9 @@ "filePaths": [ "member-access.js" ], - "sha1": "6318121ceeab8d6e2f209d2eaa8476f5c416ebeb", + "sha1": "29c4345d54f21491b5f7500da823d4753a03ab22", "gitDir": "test/corpus/repos/javascript", - "sha2": "90c11d04be5443162bc497267825252d029a3343" + "sha2": "0294e4c3c800a8463cadba06d04b734e5147da4b" } ,{ "testCaseDescription": "javascript-member-access-delete-test", @@ -252,7 +252,7 @@ 1, 1 ], - "name": "member-access.js", + "filepath": "member-access.js", "end": [ 1, 15 @@ -269,9 +269,9 @@ "filePaths": [ "member-access.js" ], - "sha1": "90c11d04be5443162bc497267825252d029a3343", + "sha1": "0294e4c3c800a8463cadba06d04b734e5147da4b", "gitDir": "test/corpus/repos/javascript", - "sha2": "ad078885ab44c7ee3d783f62cdc366251ccf8968" + "sha2": "aa83a1d624fe3d6c13b254d769115e7b67b3b811" } ,{ "testCaseDescription": "javascript-member-access-delete-rest-test", @@ -285,7 +285,7 @@ 1, 1 ], - "name": "member-access.js", + "filepath": "member-access.js", "end": [ 1, 20 @@ -302,7 +302,7 @@ "filePaths": [ "member-access.js" ], - "sha1": "ad078885ab44c7ee3d783f62cdc366251ccf8968", + "sha1": "aa83a1d624fe3d6c13b254d769115e7b67b3b811", "gitDir": "test/corpus/repos/javascript", - "sha2": "34a84c5fb21b25b173aca33ee72df362b955f3ee" + "sha2": "ca1544de272e3014ccfa6f73f73580f066b87e55" }] diff --git a/test/corpus/diff-summaries/javascript/method-call.json b/test/corpus/diff-summaries/javascript/method-call.json index 957afb5b1..beae4257e 100644 --- a/test/corpus/diff-summaries/javascript/method-call.json +++ b/test/corpus/diff-summaries/javascript/method-call.json @@ -10,7 +10,7 @@ 1, 1 ], - "name": "method-call.js", + "filepath": "method-call.js", "end": [ 1, 32 @@ -27,9 +27,9 @@ "filePaths": [ "method-call.js" ], - "sha1": "1eac526dd11d55220946d9b6306e3031c11e73a7", + "sha1": "f51ceb51189206274b7be19df66fb5dbf0d6eddc", "gitDir": "test/corpus/repos/javascript", - "sha2": "c5816345fd1905a2f4298ed7529b45295c98cf1e" + "sha2": "4789ac09ae56eb9c6e5a916a455b7335de64f8ea" } ,{ "testCaseDescription": "javascript-method-call-replacement-insert-test", @@ -43,7 +43,7 @@ 1, 1 ], - "name": "method-call.js", + "filepath": "method-call.js", "end": [ 1, 32 @@ -60,7 +60,7 @@ 2, 1 ], - "name": "method-call.js", + "filepath": "method-call.js", "end": [ 2, 32 @@ -77,9 +77,9 @@ "filePaths": [ "method-call.js" ], - "sha1": "c5816345fd1905a2f4298ed7529b45295c98cf1e", + "sha1": "4789ac09ae56eb9c6e5a916a455b7335de64f8ea", "gitDir": "test/corpus/repos/javascript", - "sha2": "42bb4713d671009105b1d9ccb7edae5cbf7b2c48" + "sha2": "840e7daa35e89d596fd5f91630bd57229b85f521" } ,{ "testCaseDescription": "javascript-method-call-delete-insert-test", @@ -94,7 +94,7 @@ 1, 25 ], - "name": "method-call.js", + "filepath": "method-call.js", "end": [ 1, 31 @@ -105,7 +105,7 @@ 1, 25 ], - "name": "method-call.js", + "filepath": "method-call.js", "end": [ 1, 31 @@ -123,9 +123,9 @@ "filePaths": [ "method-call.js" ], - "sha1": "42bb4713d671009105b1d9ccb7edae5cbf7b2c48", + "sha1": "840e7daa35e89d596fd5f91630bd57229b85f521", "gitDir": "test/corpus/repos/javascript", - "sha2": "ed18e03d391621e8d70a67e772d341e26f6465b1" + "sha2": "8bf40a24d033d5ba58c66dba0ec06b356b87eb98" } ,{ "testCaseDescription": "javascript-method-call-replacement-test", @@ -140,7 +140,7 @@ 1, 25 ], - "name": "method-call.js", + "filepath": "method-call.js", "end": [ 1, 31 @@ -151,7 +151,7 @@ 1, 25 ], - "name": "method-call.js", + "filepath": "method-call.js", "end": [ 1, 31 @@ -169,9 +169,9 @@ "filePaths": [ "method-call.js" ], - "sha1": "ed18e03d391621e8d70a67e772d341e26f6465b1", + "sha1": "8bf40a24d033d5ba58c66dba0ec06b356b87eb98", "gitDir": "test/corpus/repos/javascript", - "sha2": "0a142682630c961d9ff02801c05cc441e1dd722e" + "sha2": "5eaf3ca5ea3e95810d164a0d58e9a7e6874069ec" } ,{ "testCaseDescription": "javascript-method-call-delete-replacement-test", @@ -185,7 +185,7 @@ 1, 1 ], - "name": "method-call.js", + "filepath": "method-call.js", "end": [ 1, 32 @@ -202,7 +202,7 @@ 2, 1 ], - "name": "method-call.js", + "filepath": "method-call.js", "end": [ 2, 32 @@ -219,7 +219,7 @@ 2, 1 ], - "name": "method-call.js", + "filepath": "method-call.js", "end": [ 2, 32 @@ -236,9 +236,9 @@ "filePaths": [ "method-call.js" ], - "sha1": "0a142682630c961d9ff02801c05cc441e1dd722e", + "sha1": "5eaf3ca5ea3e95810d164a0d58e9a7e6874069ec", "gitDir": "test/corpus/repos/javascript", - "sha2": "95f9b4362d197b6e47e43cf7763c9fe06aff67f2" + "sha2": "a552504f23c0526ded3f98a77f6e6679bcf2db73" } ,{ "testCaseDescription": "javascript-method-call-delete-test", @@ -252,7 +252,7 @@ 1, 1 ], - "name": "method-call.js", + "filepath": "method-call.js", "end": [ 1, 32 @@ -269,9 +269,9 @@ "filePaths": [ "method-call.js" ], - "sha1": "95f9b4362d197b6e47e43cf7763c9fe06aff67f2", + "sha1": "a552504f23c0526ded3f98a77f6e6679bcf2db73", "gitDir": "test/corpus/repos/javascript", - "sha2": "fbd02de257a4ec83bb80fc192b629c5fd22a7ea4" + "sha2": "f84fa8487d754836daab0bea285a96bf6c8fadb0" } ,{ "testCaseDescription": "javascript-method-call-delete-rest-test", @@ -285,7 +285,7 @@ 1, 1 ], - "name": "method-call.js", + "filepath": "method-call.js", "end": [ 1, 32 @@ -302,7 +302,7 @@ "filePaths": [ "method-call.js" ], - "sha1": "fbd02de257a4ec83bb80fc192b629c5fd22a7ea4", + "sha1": "f84fa8487d754836daab0bea285a96bf6c8fadb0", "gitDir": "test/corpus/repos/javascript", - "sha2": "90687f3994b4645e5db5b97ec4da3502fbe9053d" + "sha2": "ff6e03757059860925ebb5fcfebf2f07cee6ee9f" }] diff --git a/test/corpus/diff-summaries/javascript/named-function.json b/test/corpus/diff-summaries/javascript/named-function.json index 2b13f9dfb..c16ed978c 100644 --- a/test/corpus/diff-summaries/javascript/named-function.json +++ b/test/corpus/diff-summaries/javascript/named-function.json @@ -10,7 +10,7 @@ 1, 1 ], - "name": "named-function.js", + "filepath": "named-function.js", "end": [ 1, 42 @@ -27,9 +27,9 @@ "filePaths": [ "named-function.js" ], - "sha1": "2757c3a3cfdea7d078af6cd6c05b4355fff8b112", + "sha1": "a699687c18c611424c73eb488ef4d648c874c12d", "gitDir": "test/corpus/repos/javascript", - "sha2": "661e1891e62dd3ea75b4ba1f716cf5ac3244b54a" + "sha2": "888a5f9374f9aebd626f8d17ef4258a6621402d0" } ,{ "testCaseDescription": "javascript-named-function-replacement-insert-test", @@ -43,7 +43,7 @@ 1, 1 ], - "name": "named-function.js", + "filepath": "named-function.js", "end": [ 1, 45 @@ -60,7 +60,7 @@ 2, 1 ], - "name": "named-function.js", + "filepath": "named-function.js", "end": [ 2, 42 @@ -77,9 +77,9 @@ "filePaths": [ "named-function.js" ], - "sha1": "661e1891e62dd3ea75b4ba1f716cf5ac3244b54a", + "sha1": "888a5f9374f9aebd626f8d17ef4258a6621402d0", "gitDir": "test/corpus/repos/javascript", - "sha2": "10d7a7acaf524aaf2538b4cf464b62ad3bb8cb73" + "sha2": "2b1f5bd40a042946419f4c114b501d6414ba0ecf" } ,{ "testCaseDescription": "javascript-named-function-delete-insert-test", @@ -94,7 +94,7 @@ 1, 10 ], - "name": "named-function.js", + "filepath": "named-function.js", "end": [ 1, 25 @@ -105,7 +105,7 @@ 1, 10 ], - "name": "named-function.js", + "filepath": "named-function.js", "end": [ 1, 20 @@ -123,7 +123,7 @@ 1, 21 ], - "name": "named-function.js", + "filepath": "named-function.js", "end": [ 1, 25 @@ -140,7 +140,7 @@ 1, 27 ], - "name": "named-function.js", + "filepath": "named-function.js", "end": [ 1, 31 @@ -157,7 +157,7 @@ 1, 35 ], - "name": "named-function.js", + "filepath": "named-function.js", "end": [ 1, 39 @@ -174,7 +174,7 @@ 1, 30 ], - "name": "named-function.js", + "filepath": "named-function.js", "end": [ 1, 43 @@ -191,9 +191,9 @@ "filePaths": [ "named-function.js" ], - "sha1": "10d7a7acaf524aaf2538b4cf464b62ad3bb8cb73", + "sha1": "2b1f5bd40a042946419f4c114b501d6414ba0ecf", "gitDir": "test/corpus/repos/javascript", - "sha2": "4fe44583a5a229765f67c4550e2e2a44fe5b910d" + "sha2": "eb792f3c86f13c0c49d6532cfeabd0317948d1ab" } ,{ "testCaseDescription": "javascript-named-function-replacement-test", @@ -208,7 +208,7 @@ 1, 10 ], - "name": "named-function.js", + "filepath": "named-function.js", "end": [ 1, 20 @@ -219,7 +219,7 @@ 1, 10 ], - "name": "named-function.js", + "filepath": "named-function.js", "end": [ 1, 25 @@ -237,7 +237,7 @@ 1, 21 ], - "name": "named-function.js", + "filepath": "named-function.js", "end": [ 1, 25 @@ -254,7 +254,7 @@ 1, 27 ], - "name": "named-function.js", + "filepath": "named-function.js", "end": [ 1, 31 @@ -271,7 +271,7 @@ 1, 30 ], - "name": "named-function.js", + "filepath": "named-function.js", "end": [ 1, 43 @@ -288,7 +288,7 @@ 1, 35 ], - "name": "named-function.js", + "filepath": "named-function.js", "end": [ 1, 39 @@ -305,9 +305,9 @@ "filePaths": [ "named-function.js" ], - "sha1": "4fe44583a5a229765f67c4550e2e2a44fe5b910d", + "sha1": "eb792f3c86f13c0c49d6532cfeabd0317948d1ab", "gitDir": "test/corpus/repos/javascript", - "sha2": "cfb65cb4c10bef064b3811d6d74daa567401b303" + "sha2": "f51ac41939b86e1c17478a7febdc011720a423a1" } ,{ "testCaseDescription": "javascript-named-function-delete-replacement-test", @@ -321,7 +321,7 @@ 1, 1 ], - "name": "named-function.js", + "filepath": "named-function.js", "end": [ 1, 45 @@ -338,7 +338,7 @@ 2, 1 ], - "name": "named-function.js", + "filepath": "named-function.js", "end": [ 2, 42 @@ -355,7 +355,7 @@ 2, 1 ], - "name": "named-function.js", + "filepath": "named-function.js", "end": [ 2, 45 @@ -372,9 +372,9 @@ "filePaths": [ "named-function.js" ], - "sha1": "cfb65cb4c10bef064b3811d6d74daa567401b303", + "sha1": "f51ac41939b86e1c17478a7febdc011720a423a1", "gitDir": "test/corpus/repos/javascript", - "sha2": "1fee1c5ce1f374dd5f6fc565a5a95e51c849368f" + "sha2": "16e0a14cde4c464e72035bd8822c4afb4ed4678b" } ,{ "testCaseDescription": "javascript-named-function-delete-test", @@ -388,7 +388,7 @@ 1, 1 ], - "name": "named-function.js", + "filepath": "named-function.js", "end": [ 1, 42 @@ -405,9 +405,9 @@ "filePaths": [ "named-function.js" ], - "sha1": "1fee1c5ce1f374dd5f6fc565a5a95e51c849368f", + "sha1": "16e0a14cde4c464e72035bd8822c4afb4ed4678b", "gitDir": "test/corpus/repos/javascript", - "sha2": "f4a8c0642e5045127f2f450d9762276ffcb136b2" + "sha2": "ccb988d6c2d99f622210bcffe2ba546e92169d92" } ,{ "testCaseDescription": "javascript-named-function-delete-rest-test", @@ -421,7 +421,7 @@ 1, 1 ], - "name": "named-function.js", + "filepath": "named-function.js", "end": [ 1, 45 @@ -438,7 +438,7 @@ "filePaths": [ "named-function.js" ], - "sha1": "f4a8c0642e5045127f2f450d9762276ffcb136b2", + "sha1": "ccb988d6c2d99f622210bcffe2ba546e92169d92", "gitDir": "test/corpus/repos/javascript", - "sha2": "035ebadb21075a55367b83c380264365799ac421" + "sha2": "e5bc155d380e9bf97868b601622f7c6eab1c99c8" }] diff --git a/test/corpus/diff-summaries/javascript/nested-functions.json b/test/corpus/diff-summaries/javascript/nested-functions.json index 9c62b516f..c37ecffde 100644 --- a/test/corpus/diff-summaries/javascript/nested-functions.json +++ b/test/corpus/diff-summaries/javascript/nested-functions.json @@ -10,7 +10,7 @@ 1, 1 ], - "name": "nested-functions.js", + "filepath": "nested-functions.js", "end": [ 1, 103 @@ -27,9 +27,9 @@ "filePaths": [ "nested-functions.js" ], - "sha1": "ff9c3e1416340f9c41efe59880ae44b658ff4bf3", + "sha1": "57fc79f4496e63c2f0dfb87d911391771786a8cd", "gitDir": "test/corpus/repos/javascript", - "sha2": "fda28c0db6815d7395f08564645db20bef73cc87" + "sha2": "59e20a1c48daece9d2df4541e1fdeff0dd73e80e" } ,{ "testCaseDescription": "javascript-nested-functions-replacement-insert-test", @@ -43,7 +43,7 @@ 1, 1 ], - "name": "nested-functions.js", + "filepath": "nested-functions.js", "end": [ 1, 103 @@ -60,7 +60,7 @@ 2, 1 ], - "name": "nested-functions.js", + "filepath": "nested-functions.js", "end": [ 2, 103 @@ -77,9 +77,9 @@ "filePaths": [ "nested-functions.js" ], - "sha1": "fda28c0db6815d7395f08564645db20bef73cc87", + "sha1": "59e20a1c48daece9d2df4541e1fdeff0dd73e80e", "gitDir": "test/corpus/repos/javascript", - "sha2": "e0170503b1eef4379585fcadaab5c1ce210fac28" + "sha2": "396d7dfc3fe97c43ffede2fea8cf95bfd6a4a144" } ,{ "testCaseDescription": "javascript-nested-functions-delete-insert-test", @@ -94,7 +94,7 @@ 1, 74 ], - "name": "nested-functions.js", + "filepath": "nested-functions.js", "end": [ 1, 78 @@ -105,7 +105,7 @@ 1, 74 ], - "name": "nested-functions.js", + "filepath": "nested-functions.js", "end": [ 1, 78 @@ -124,7 +124,7 @@ 1, 93 ], - "name": "nested-functions.js", + "filepath": "nested-functions.js", "end": [ 1, 97 @@ -135,7 +135,7 @@ 1, 93 ], - "name": "nested-functions.js", + "filepath": "nested-functions.js", "end": [ 1, 97 @@ -153,9 +153,9 @@ "filePaths": [ "nested-functions.js" ], - "sha1": "e0170503b1eef4379585fcadaab5c1ce210fac28", + "sha1": "396d7dfc3fe97c43ffede2fea8cf95bfd6a4a144", "gitDir": "test/corpus/repos/javascript", - "sha2": "62a15249f8533d75e77e361ae05bd39673511d2d" + "sha2": "9c7a5d76d469dda935501f03b0aeaf3fb7ced6d4" } ,{ "testCaseDescription": "javascript-nested-functions-replacement-test", @@ -170,7 +170,7 @@ 1, 74 ], - "name": "nested-functions.js", + "filepath": "nested-functions.js", "end": [ 1, 78 @@ -181,7 +181,7 @@ 1, 74 ], - "name": "nested-functions.js", + "filepath": "nested-functions.js", "end": [ 1, 78 @@ -200,7 +200,7 @@ 1, 93 ], - "name": "nested-functions.js", + "filepath": "nested-functions.js", "end": [ 1, 97 @@ -211,7 +211,7 @@ 1, 93 ], - "name": "nested-functions.js", + "filepath": "nested-functions.js", "end": [ 1, 97 @@ -229,9 +229,9 @@ "filePaths": [ "nested-functions.js" ], - "sha1": "62a15249f8533d75e77e361ae05bd39673511d2d", + "sha1": "9c7a5d76d469dda935501f03b0aeaf3fb7ced6d4", "gitDir": "test/corpus/repos/javascript", - "sha2": "04f144c9e7008a1fe76b333c0622cada2893f709" + "sha2": "2a2cc5ee7b6fff876b0f792f06bef30465d69d57" } ,{ "testCaseDescription": "javascript-nested-functions-delete-replacement-test", @@ -245,7 +245,7 @@ 1, 1 ], - "name": "nested-functions.js", + "filepath": "nested-functions.js", "end": [ 1, 103 @@ -262,7 +262,7 @@ 2, 1 ], - "name": "nested-functions.js", + "filepath": "nested-functions.js", "end": [ 2, 103 @@ -279,7 +279,7 @@ 2, 1 ], - "name": "nested-functions.js", + "filepath": "nested-functions.js", "end": [ 2, 103 @@ -296,9 +296,9 @@ "filePaths": [ "nested-functions.js" ], - "sha1": "04f144c9e7008a1fe76b333c0622cada2893f709", + "sha1": "2a2cc5ee7b6fff876b0f792f06bef30465d69d57", "gitDir": "test/corpus/repos/javascript", - "sha2": "0483a9c0ff8b154901197bcab0131839cf906edc" + "sha2": "a755ce1f6bfa76445de62eb779da89cb82486801" } ,{ "testCaseDescription": "javascript-nested-functions-delete-test", @@ -312,7 +312,7 @@ 1, 1 ], - "name": "nested-functions.js", + "filepath": "nested-functions.js", "end": [ 1, 103 @@ -329,9 +329,9 @@ "filePaths": [ "nested-functions.js" ], - "sha1": "0483a9c0ff8b154901197bcab0131839cf906edc", + "sha1": "a755ce1f6bfa76445de62eb779da89cb82486801", "gitDir": "test/corpus/repos/javascript", - "sha2": "a15f05c7885e2efa3515f753ffe6109f2c7430cd" + "sha2": "1b522ec030c0decf1c99062d0d9b12ae130ad41a" } ,{ "testCaseDescription": "javascript-nested-functions-delete-rest-test", @@ -345,7 +345,7 @@ 1, 1 ], - "name": "nested-functions.js", + "filepath": "nested-functions.js", "end": [ 1, 103 @@ -362,7 +362,7 @@ "filePaths": [ "nested-functions.js" ], - "sha1": "a15f05c7885e2efa3515f753ffe6109f2c7430cd", + "sha1": "1b522ec030c0decf1c99062d0d9b12ae130ad41a", "gitDir": "test/corpus/repos/javascript", - "sha2": "215d10e67e03c8e29f188758043ace6b619b01e5" + "sha2": "a3a08cd066a70c6588e4455ec60aec9b2dcae473" }] diff --git a/test/corpus/diff-summaries/javascript/null.json b/test/corpus/diff-summaries/javascript/null.json index 2c840d20a..e6c648c86 100644 --- a/test/corpus/diff-summaries/javascript/null.json +++ b/test/corpus/diff-summaries/javascript/null.json @@ -10,7 +10,7 @@ 1, 1 ], - "name": "null.js", + "filepath": "null.js", "end": [ 1, 5 @@ -27,9 +27,9 @@ "filePaths": [ "null.js" ], - "sha1": "71b405a91807f07e6c1c55a71a93c78d07b0b4ab", + "sha1": "8540d7af721429195043bd3005c00e3713220c39", "gitDir": "test/corpus/repos/javascript", - "sha2": "40b103a73134c60adc6ee3ae4902918373b060cf" + "sha2": "93c72c64eca26a667db90a211a096d676bf318fb" } ,{ "testCaseDescription": "javascript-null-replacement-insert-test", @@ -43,7 +43,7 @@ 1, 1 ], - "name": "null.js", + "filepath": "null.js", "end": [ 1, 13 @@ -60,7 +60,7 @@ 2, 1 ], - "name": "null.js", + "filepath": "null.js", "end": [ 2, 5 @@ -77,9 +77,9 @@ "filePaths": [ "null.js" ], - "sha1": "40b103a73134c60adc6ee3ae4902918373b060cf", + "sha1": "93c72c64eca26a667db90a211a096d676bf318fb", "gitDir": "test/corpus/repos/javascript", - "sha2": "39f88f076256d48c52a7b49d2e2a4dbb33b65e1a" + "sha2": "eecf7bbf0e848b23e01ae924b14a60efb17196b4" } ,{ "testCaseDescription": "javascript-null-delete-insert-test", @@ -93,7 +93,7 @@ 1, 1 ], - "name": "null.js", + "filepath": "null.js", "end": [ 1, 5 @@ -110,7 +110,7 @@ 1, 1 ], - "name": "null.js", + "filepath": "null.js", "end": [ 1, 13 @@ -127,9 +127,9 @@ "filePaths": [ "null.js" ], - "sha1": "39f88f076256d48c52a7b49d2e2a4dbb33b65e1a", + "sha1": "eecf7bbf0e848b23e01ae924b14a60efb17196b4", "gitDir": "test/corpus/repos/javascript", - "sha2": "a0b7643968ebb1985deac3297be5a63e84c87ec5" + "sha2": "18073d45e88081955aa5da86dfaac3141c7b593d" } ,{ "testCaseDescription": "javascript-null-replacement-test", @@ -143,7 +143,7 @@ 1, 1 ], - "name": "null.js", + "filepath": "null.js", "end": [ 1, 13 @@ -160,7 +160,7 @@ 1, 1 ], - "name": "null.js", + "filepath": "null.js", "end": [ 1, 5 @@ -177,9 +177,9 @@ "filePaths": [ "null.js" ], - "sha1": "a0b7643968ebb1985deac3297be5a63e84c87ec5", + "sha1": "18073d45e88081955aa5da86dfaac3141c7b593d", "gitDir": "test/corpus/repos/javascript", - "sha2": "b398a1a9095f31c9f49eb70f76ab7775e0e0b912" + "sha2": "198209e9c0f93699ad53dc47e775cd90c2d88b35" } ,{ "testCaseDescription": "javascript-null-delete-replacement-test", @@ -193,7 +193,7 @@ 1, 1 ], - "name": "null.js", + "filepath": "null.js", "end": [ 1, 13 @@ -210,7 +210,7 @@ 2, 1 ], - "name": "null.js", + "filepath": "null.js", "end": [ 2, 5 @@ -227,7 +227,7 @@ 2, 1 ], - "name": "null.js", + "filepath": "null.js", "end": [ 2, 13 @@ -244,9 +244,9 @@ "filePaths": [ "null.js" ], - "sha1": "b398a1a9095f31c9f49eb70f76ab7775e0e0b912", + "sha1": "198209e9c0f93699ad53dc47e775cd90c2d88b35", "gitDir": "test/corpus/repos/javascript", - "sha2": "9eef1322e7b1b0997a712803355e071fd0cb12da" + "sha2": "7b43f93904a6162c4f9b61d4959d1cce8d33348d" } ,{ "testCaseDescription": "javascript-null-delete-test", @@ -260,7 +260,7 @@ 1, 1 ], - "name": "null.js", + "filepath": "null.js", "end": [ 1, 5 @@ -277,9 +277,9 @@ "filePaths": [ "null.js" ], - "sha1": "9eef1322e7b1b0997a712803355e071fd0cb12da", + "sha1": "7b43f93904a6162c4f9b61d4959d1cce8d33348d", "gitDir": "test/corpus/repos/javascript", - "sha2": "48fea5e1448dcc23d6a626649dec8cdedc67a029" + "sha2": "9d63dd64268183fbb85c550dc1fb462923c695da" } ,{ "testCaseDescription": "javascript-null-delete-rest-test", @@ -293,7 +293,7 @@ 1, 1 ], - "name": "null.js", + "filepath": "null.js", "end": [ 1, 13 @@ -310,7 +310,7 @@ "filePaths": [ "null.js" ], - "sha1": "48fea5e1448dcc23d6a626649dec8cdedc67a029", + "sha1": "9d63dd64268183fbb85c550dc1fb462923c695da", "gitDir": "test/corpus/repos/javascript", - "sha2": "b12ee7f9618c46965c38b2ba972b8dc99f4db063" + "sha2": "c416941f9ad227e04563dc7724f287893f6a1189" }] diff --git a/test/corpus/diff-summaries/javascript/number.json b/test/corpus/diff-summaries/javascript/number.json index 9b36290bb..cb450003a 100644 --- a/test/corpus/diff-summaries/javascript/number.json +++ b/test/corpus/diff-summaries/javascript/number.json @@ -10,7 +10,7 @@ 1, 1 ], - "name": "number.js", + "filepath": "number.js", "end": [ 1, 4 @@ -27,9 +27,9 @@ "filePaths": [ "number.js" ], - "sha1": "c0f927bdea55b3ee78ee68522ae964808f19fab6", + "sha1": "2acfa94e8da24a348a707bf9de50ba1b017c23b7", "gitDir": "test/corpus/repos/javascript", - "sha2": "14a7034f5e599408ea3a07f7c55fc2713442de61" + "sha2": "ae619f3a64aa79d8b2b9899ff54266136cdd6ad8" } ,{ "testCaseDescription": "javascript-number-replacement-insert-test", @@ -43,7 +43,7 @@ 1, 1 ], - "name": "number.js", + "filepath": "number.js", "end": [ 1, 4 @@ -60,7 +60,7 @@ 2, 1 ], - "name": "number.js", + "filepath": "number.js", "end": [ 2, 4 @@ -77,9 +77,9 @@ "filePaths": [ "number.js" ], - "sha1": "14a7034f5e599408ea3a07f7c55fc2713442de61", + "sha1": "ae619f3a64aa79d8b2b9899ff54266136cdd6ad8", "gitDir": "test/corpus/repos/javascript", - "sha2": "cdcfd757586d10a50ea65fad6be0095c3ff0e599" + "sha2": "7d8f74947661866841045383aa8a7feb74319f6a" } ,{ "testCaseDescription": "javascript-number-delete-insert-test", @@ -94,7 +94,7 @@ 1, 1 ], - "name": "number.js", + "filepath": "number.js", "end": [ 1, 4 @@ -105,7 +105,7 @@ 1, 1 ], - "name": "number.js", + "filepath": "number.js", "end": [ 1, 4 @@ -123,9 +123,9 @@ "filePaths": [ "number.js" ], - "sha1": "cdcfd757586d10a50ea65fad6be0095c3ff0e599", + "sha1": "7d8f74947661866841045383aa8a7feb74319f6a", "gitDir": "test/corpus/repos/javascript", - "sha2": "92ac8953b06044880a975cf28d3c45aab8f88759" + "sha2": "43650ac02b3ba005be893ce6bedf110047b3954a" } ,{ "testCaseDescription": "javascript-number-replacement-test", @@ -140,7 +140,7 @@ 1, 1 ], - "name": "number.js", + "filepath": "number.js", "end": [ 1, 4 @@ -151,7 +151,7 @@ 1, 1 ], - "name": "number.js", + "filepath": "number.js", "end": [ 1, 4 @@ -169,9 +169,9 @@ "filePaths": [ "number.js" ], - "sha1": "92ac8953b06044880a975cf28d3c45aab8f88759", + "sha1": "43650ac02b3ba005be893ce6bedf110047b3954a", "gitDir": "test/corpus/repos/javascript", - "sha2": "dffbcecbd65965443b71665de242c237f4d94513" + "sha2": "9b7f3f4e75505c5af698fa82631bef4a2cd1ce9c" } ,{ "testCaseDescription": "javascript-number-delete-replacement-test", @@ -185,7 +185,7 @@ 1, 1 ], - "name": "number.js", + "filepath": "number.js", "end": [ 1, 4 @@ -202,7 +202,7 @@ 2, 1 ], - "name": "number.js", + "filepath": "number.js", "end": [ 2, 4 @@ -219,7 +219,7 @@ 2, 1 ], - "name": "number.js", + "filepath": "number.js", "end": [ 2, 4 @@ -236,9 +236,9 @@ "filePaths": [ "number.js" ], - "sha1": "dffbcecbd65965443b71665de242c237f4d94513", + "sha1": "9b7f3f4e75505c5af698fa82631bef4a2cd1ce9c", "gitDir": "test/corpus/repos/javascript", - "sha2": "fab30a6c3846d6d9ae795337b13541ab3591bf7d" + "sha2": "83d6d0ed80822443dd93596a874ac61d2535f887" } ,{ "testCaseDescription": "javascript-number-delete-test", @@ -252,7 +252,7 @@ 1, 1 ], - "name": "number.js", + "filepath": "number.js", "end": [ 1, 4 @@ -269,9 +269,9 @@ "filePaths": [ "number.js" ], - "sha1": "fab30a6c3846d6d9ae795337b13541ab3591bf7d", + "sha1": "83d6d0ed80822443dd93596a874ac61d2535f887", "gitDir": "test/corpus/repos/javascript", - "sha2": "e3a519863f7404783c22937eac4ab659a4f30f0d" + "sha2": "c87329f7b1c138371e0c7d5ede428a24dc2ec72a" } ,{ "testCaseDescription": "javascript-number-delete-rest-test", @@ -285,7 +285,7 @@ 1, 1 ], - "name": "number.js", + "filepath": "number.js", "end": [ 1, 4 @@ -302,7 +302,7 @@ "filePaths": [ "number.js" ], - "sha1": "e3a519863f7404783c22937eac4ab659a4f30f0d", + "sha1": "c87329f7b1c138371e0c7d5ede428a24dc2ec72a", "gitDir": "test/corpus/repos/javascript", - "sha2": "76561264ab91701d52dcc8dcbb42c25ea412ae25" + "sha2": "c7c169b7ce7f391b61032220b32c3d8660c33c84" }] diff --git a/test/corpus/diff-summaries/javascript/object-with-methods.json b/test/corpus/diff-summaries/javascript/object-with-methods.json index 0db29037c..b303b52fe 100644 --- a/test/corpus/diff-summaries/javascript/object-with-methods.json +++ b/test/corpus/diff-summaries/javascript/object-with-methods.json @@ -10,7 +10,7 @@ 1, 1 ], - "name": "objects-with-methods.js", + "filepath": "objects-with-methods.js", "end": [ 1, 32 @@ -27,9 +27,9 @@ "filePaths": [ "objects-with-methods.js" ], - "sha1": "2a302d002490d7bb5aff372747a028cec52c1b4b", + "sha1": "60d58ef967f1fcdba8a3411ada06cb5b8a24d2f4", "gitDir": "test/corpus/repos/javascript", - "sha2": "6783a5e813844940dfff6c5636d1461bede9ad38" + "sha2": "c3e3c6374ed1ffa54c4772f56e41249656c79627" } ,{ "testCaseDescription": "javascript-objects-with-methods-replacement-insert-test", @@ -43,7 +43,7 @@ 1, 1 ], - "name": "objects-with-methods.js", + "filepath": "objects-with-methods.js", "end": [ 1, 37 @@ -60,7 +60,7 @@ 2, 1 ], - "name": "objects-with-methods.js", + "filepath": "objects-with-methods.js", "end": [ 2, 32 @@ -77,9 +77,9 @@ "filePaths": [ "objects-with-methods.js" ], - "sha1": "6783a5e813844940dfff6c5636d1461bede9ad38", + "sha1": "c3e3c6374ed1ffa54c4772f56e41249656c79627", "gitDir": "test/corpus/repos/javascript", - "sha2": "a213d7d3cf0a804f759d6137db7182fe97a95f1a" + "sha2": "43bff48a1143b1dc83dd1a5a6f8085f8b7e64b55" } ,{ "testCaseDescription": "javascript-objects-with-methods-delete-insert-test", @@ -94,7 +94,7 @@ 1, 3 ], - "name": "objects-with-methods.js", + "filepath": "objects-with-methods.js", "end": [ 1, 11 @@ -105,7 +105,7 @@ 1, 3 ], - "name": "objects-with-methods.js", + "filepath": "objects-with-methods.js", "end": [ 1, 6 @@ -123,9 +123,9 @@ "filePaths": [ "objects-with-methods.js" ], - "sha1": "a213d7d3cf0a804f759d6137db7182fe97a95f1a", + "sha1": "43bff48a1143b1dc83dd1a5a6f8085f8b7e64b55", "gitDir": "test/corpus/repos/javascript", - "sha2": "b118e4745f2ffd7e7f6d1f9247ec62a7a7a6de21" + "sha2": "3d82ad3c505c4cc1f9b740c2ff03e4dad09927aa" } ,{ "testCaseDescription": "javascript-objects-with-methods-replacement-test", @@ -140,7 +140,7 @@ 1, 3 ], - "name": "objects-with-methods.js", + "filepath": "objects-with-methods.js", "end": [ 1, 6 @@ -151,7 +151,7 @@ 1, 3 ], - "name": "objects-with-methods.js", + "filepath": "objects-with-methods.js", "end": [ 1, 11 @@ -169,9 +169,9 @@ "filePaths": [ "objects-with-methods.js" ], - "sha1": "b118e4745f2ffd7e7f6d1f9247ec62a7a7a6de21", + "sha1": "3d82ad3c505c4cc1f9b740c2ff03e4dad09927aa", "gitDir": "test/corpus/repos/javascript", - "sha2": "856aa7174277d2af3db156663841364743743bf8" + "sha2": "dadae4a3596566e52c0fc77e1ac177a84bdc5323" } ,{ "testCaseDescription": "javascript-objects-with-methods-delete-replacement-test", @@ -185,7 +185,7 @@ 1, 1 ], - "name": "objects-with-methods.js", + "filepath": "objects-with-methods.js", "end": [ 1, 37 @@ -202,7 +202,7 @@ 2, 1 ], - "name": "objects-with-methods.js", + "filepath": "objects-with-methods.js", "end": [ 2, 32 @@ -219,7 +219,7 @@ 2, 1 ], - "name": "objects-with-methods.js", + "filepath": "objects-with-methods.js", "end": [ 2, 37 @@ -236,9 +236,9 @@ "filePaths": [ "objects-with-methods.js" ], - "sha1": "856aa7174277d2af3db156663841364743743bf8", + "sha1": "dadae4a3596566e52c0fc77e1ac177a84bdc5323", "gitDir": "test/corpus/repos/javascript", - "sha2": "9f4f98182b4ee3099d8c8b9437ab3970278a211f" + "sha2": "be7220faa8ef465c3abe4157f039237192f97ce8" } ,{ "testCaseDescription": "javascript-objects-with-methods-delete-test", @@ -252,7 +252,7 @@ 1, 1 ], - "name": "objects-with-methods.js", + "filepath": "objects-with-methods.js", "end": [ 1, 32 @@ -269,9 +269,9 @@ "filePaths": [ "objects-with-methods.js" ], - "sha1": "9f4f98182b4ee3099d8c8b9437ab3970278a211f", + "sha1": "be7220faa8ef465c3abe4157f039237192f97ce8", "gitDir": "test/corpus/repos/javascript", - "sha2": "fc6f3cd8022124b7746e923db660ebaf4ab20072" + "sha2": "f6204101d9552858d2f5197316f65a7a12a7828f" } ,{ "testCaseDescription": "javascript-objects-with-methods-delete-rest-test", @@ -285,7 +285,7 @@ 1, 1 ], - "name": "objects-with-methods.js", + "filepath": "objects-with-methods.js", "end": [ 1, 37 @@ -302,7 +302,7 @@ "filePaths": [ "objects-with-methods.js" ], - "sha1": "fc6f3cd8022124b7746e923db660ebaf4ab20072", + "sha1": "f6204101d9552858d2f5197316f65a7a12a7828f", "gitDir": "test/corpus/repos/javascript", - "sha2": "802ec5ac85b69eebd846079cc2cd500021a32d84" + "sha2": "6aa9ad44c07a06cdd1545eaef568bbb138652cdb" }] diff --git a/test/corpus/diff-summaries/javascript/object.json b/test/corpus/diff-summaries/javascript/object.json index 20c277693..58a4ac1b6 100644 --- a/test/corpus/diff-summaries/javascript/object.json +++ b/test/corpus/diff-summaries/javascript/object.json @@ -10,7 +10,7 @@ 1, 1 ], - "name": "object.js", + "filepath": "object.js", "end": [ 1, 21 @@ -27,9 +27,9 @@ "filePaths": [ "object.js" ], - "sha1": "f7d88a07b742fd7334d28806f01764ddfed94384", + "sha1": "1b4f57cfac8417f168e3ab820d321029ac522ca8", "gitDir": "test/corpus/repos/javascript", - "sha2": "6f8bef4abc5e31e04a543d36be2551dde44e550e" + "sha2": "6abc7ad0c6b8ae2a549c43af67628d709e7cd8b1" } ,{ "testCaseDescription": "javascript-object-replacement-insert-test", @@ -43,7 +43,7 @@ 1, 1 ], - "name": "object.js", + "filepath": "object.js", "end": [ 1, 54 @@ -60,7 +60,7 @@ 2, 1 ], - "name": "object.js", + "filepath": "object.js", "end": [ 2, 21 @@ -77,9 +77,9 @@ "filePaths": [ "object.js" ], - "sha1": "6f8bef4abc5e31e04a543d36be2551dde44e550e", + "sha1": "6abc7ad0c6b8ae2a549c43af67628d709e7cd8b1", "gitDir": "test/corpus/repos/javascript", - "sha2": "d7474d4e8300f28a199a968e552de8cae6044b36" + "sha2": "c7222a5f704a94e8287ac06adde5ffc82bfa71a8" } ,{ "testCaseDescription": "javascript-object-delete-insert-test", @@ -93,7 +93,7 @@ 1, 21 ], - "name": "object.js", + "filepath": "object.js", "end": [ 1, 37 @@ -110,7 +110,7 @@ 1, 39 ], - "name": "object.js", + "filepath": "object.js", "end": [ 1, 52 @@ -127,9 +127,9 @@ "filePaths": [ "object.js" ], - "sha1": "d7474d4e8300f28a199a968e552de8cae6044b36", + "sha1": "c7222a5f704a94e8287ac06adde5ffc82bfa71a8", "gitDir": "test/corpus/repos/javascript", - "sha2": "e10e21b2d9e5e12c61cc17240c59db19ef0d10f7" + "sha2": "e54491511c1fef0c0c8941288366373d5b44313f" } ,{ "testCaseDescription": "javascript-object-replacement-test", @@ -143,7 +143,7 @@ 1, 21 ], - "name": "object.js", + "filepath": "object.js", "end": [ 1, 37 @@ -160,7 +160,7 @@ 1, 39 ], - "name": "object.js", + "filepath": "object.js", "end": [ 1, 52 @@ -177,9 +177,9 @@ "filePaths": [ "object.js" ], - "sha1": "e10e21b2d9e5e12c61cc17240c59db19ef0d10f7", + "sha1": "e54491511c1fef0c0c8941288366373d5b44313f", "gitDir": "test/corpus/repos/javascript", - "sha2": "a7ec58724bdc2f71f12594b83ff1dced76cd1bad" + "sha2": "019782a8597ca72f22180c4db541182e3ae872f5" } ,{ "testCaseDescription": "javascript-object-delete-replacement-test", @@ -193,7 +193,7 @@ 1, 1 ], - "name": "object.js", + "filepath": "object.js", "end": [ 1, 54 @@ -210,7 +210,7 @@ 2, 1 ], - "name": "object.js", + "filepath": "object.js", "end": [ 2, 21 @@ -227,7 +227,7 @@ 2, 1 ], - "name": "object.js", + "filepath": "object.js", "end": [ 2, 54 @@ -244,9 +244,9 @@ "filePaths": [ "object.js" ], - "sha1": "a7ec58724bdc2f71f12594b83ff1dced76cd1bad", + "sha1": "019782a8597ca72f22180c4db541182e3ae872f5", "gitDir": "test/corpus/repos/javascript", - "sha2": "98d31f1f5f2777d2fe89a14ae0d81f6c8b45f98c" + "sha2": "9d3a32337c68d56e898e3f79cae920917977c3dc" } ,{ "testCaseDescription": "javascript-object-delete-test", @@ -260,7 +260,7 @@ 1, 1 ], - "name": "object.js", + "filepath": "object.js", "end": [ 1, 21 @@ -277,9 +277,9 @@ "filePaths": [ "object.js" ], - "sha1": "98d31f1f5f2777d2fe89a14ae0d81f6c8b45f98c", + "sha1": "9d3a32337c68d56e898e3f79cae920917977c3dc", "gitDir": "test/corpus/repos/javascript", - "sha2": "8a4a15f9fb5e7993a6e63395aaac3542401d72e2" + "sha2": "e5889419240970710a2958332ed72fba51bf3deb" } ,{ "testCaseDescription": "javascript-object-delete-rest-test", @@ -293,7 +293,7 @@ 1, 1 ], - "name": "object.js", + "filepath": "object.js", "end": [ 1, 54 @@ -310,7 +310,7 @@ "filePaths": [ "object.js" ], - "sha1": "8a4a15f9fb5e7993a6e63395aaac3542401d72e2", + "sha1": "e5889419240970710a2958332ed72fba51bf3deb", "gitDir": "test/corpus/repos/javascript", - "sha2": "804f2056b155a51e98aacc2af9f2950bab4cbaf8" + "sha2": "4f51ffb21d44954d5c9b1c783a7281134da74d7a" }] diff --git a/test/corpus/diff-summaries/javascript/regex.json b/test/corpus/diff-summaries/javascript/regex.json index 776a208e9..acbc585ff 100644 --- a/test/corpus/diff-summaries/javascript/regex.json +++ b/test/corpus/diff-summaries/javascript/regex.json @@ -10,7 +10,7 @@ 1, 1 ], - "name": "regex.js", + "filepath": "regex.js", "end": [ 1, 7 @@ -27,9 +27,9 @@ "filePaths": [ "regex.js" ], - "sha1": "a2484cda906ab54500ff1a38755f0f7a37c85d77", + "sha1": "f5b91915cdfaa0a8c913ae799e721f71f579a5fa", "gitDir": "test/corpus/repos/javascript", - "sha2": "ba99759f9b455baaea534db57c0a9bbdf4e784ee" + "sha2": "f5f23a9f1bd83ec19a51dfd4b86a8cd684a60abc" } ,{ "testCaseDescription": "javascript-regex-replacement-insert-test", @@ -43,7 +43,7 @@ 1, 1 ], - "name": "regex.js", + "filepath": "regex.js", "end": [ 1, 15 @@ -60,7 +60,7 @@ 2, 1 ], - "name": "regex.js", + "filepath": "regex.js", "end": [ 2, 7 @@ -77,9 +77,9 @@ "filePaths": [ "regex.js" ], - "sha1": "ba99759f9b455baaea534db57c0a9bbdf4e784ee", + "sha1": "f5f23a9f1bd83ec19a51dfd4b86a8cd684a60abc", "gitDir": "test/corpus/repos/javascript", - "sha2": "f89564bc9c495fc245321efc7ce2f893282252f1" + "sha2": "dcd7255476e861d37c3affa4615d3755f0e4fc70" } ,{ "testCaseDescription": "javascript-regex-delete-insert-test", @@ -94,7 +94,7 @@ 1, 1 ], - "name": "regex.js", + "filepath": "regex.js", "end": [ 1, 15 @@ -105,7 +105,7 @@ 1, 1 ], - "name": "regex.js", + "filepath": "regex.js", "end": [ 1, 7 @@ -123,9 +123,9 @@ "filePaths": [ "regex.js" ], - "sha1": "f89564bc9c495fc245321efc7ce2f893282252f1", + "sha1": "dcd7255476e861d37c3affa4615d3755f0e4fc70", "gitDir": "test/corpus/repos/javascript", - "sha2": "246cd5b7f230ebefe2653bf0567625dfab2b0b64" + "sha2": "047d2bb2c6a6e3e8dec2f409d8d09db9a57c98a3" } ,{ "testCaseDescription": "javascript-regex-replacement-test", @@ -140,7 +140,7 @@ 1, 1 ], - "name": "regex.js", + "filepath": "regex.js", "end": [ 1, 7 @@ -151,7 +151,7 @@ 1, 1 ], - "name": "regex.js", + "filepath": "regex.js", "end": [ 1, 15 @@ -169,9 +169,9 @@ "filePaths": [ "regex.js" ], - "sha1": "246cd5b7f230ebefe2653bf0567625dfab2b0b64", + "sha1": "047d2bb2c6a6e3e8dec2f409d8d09db9a57c98a3", "gitDir": "test/corpus/repos/javascript", - "sha2": "20f06465056f68cd4dbd3da5f65b5e1e61a5f2a3" + "sha2": "f34c20c636bf30bf41907697ab12cbc6f6bc4da6" } ,{ "testCaseDescription": "javascript-regex-delete-replacement-test", @@ -185,7 +185,7 @@ 1, 1 ], - "name": "regex.js", + "filepath": "regex.js", "end": [ 1, 15 @@ -202,7 +202,7 @@ 2, 1 ], - "name": "regex.js", + "filepath": "regex.js", "end": [ 2, 7 @@ -219,7 +219,7 @@ 2, 1 ], - "name": "regex.js", + "filepath": "regex.js", "end": [ 2, 15 @@ -236,9 +236,9 @@ "filePaths": [ "regex.js" ], - "sha1": "20f06465056f68cd4dbd3da5f65b5e1e61a5f2a3", + "sha1": "f34c20c636bf30bf41907697ab12cbc6f6bc4da6", "gitDir": "test/corpus/repos/javascript", - "sha2": "1adb4501e159734dc46acc505ee11e5a633493a7" + "sha2": "78af2a30b3658ea4285dd231eb350f6d22a5f894" } ,{ "testCaseDescription": "javascript-regex-delete-test", @@ -252,7 +252,7 @@ 1, 1 ], - "name": "regex.js", + "filepath": "regex.js", "end": [ 1, 7 @@ -269,9 +269,9 @@ "filePaths": [ "regex.js" ], - "sha1": "1adb4501e159734dc46acc505ee11e5a633493a7", + "sha1": "78af2a30b3658ea4285dd231eb350f6d22a5f894", "gitDir": "test/corpus/repos/javascript", - "sha2": "04bdd6c2c747af7d555e7dc76c31bcb840ffa7e5" + "sha2": "d2697be3fc6cd1f0439a66a84ae8791ac7b24081" } ,{ "testCaseDescription": "javascript-regex-delete-rest-test", @@ -285,7 +285,7 @@ 1, 1 ], - "name": "regex.js", + "filepath": "regex.js", "end": [ 1, 15 @@ -302,7 +302,7 @@ "filePaths": [ "regex.js" ], - "sha1": "04bdd6c2c747af7d555e7dc76c31bcb840ffa7e5", + "sha1": "d2697be3fc6cd1f0439a66a84ae8791ac7b24081", "gitDir": "test/corpus/repos/javascript", - "sha2": "88eddedb2d7666ebcc74cb1693e7f24e13e4e481" + "sha2": "18c86bb6fad549661412ad8c3e67e3e4a4fb7e2b" }] diff --git a/test/corpus/diff-summaries/javascript/relational-operator.json b/test/corpus/diff-summaries/javascript/relational-operator.json index 27e1eb088..b00bf7c7d 100644 --- a/test/corpus/diff-summaries/javascript/relational-operator.json +++ b/test/corpus/diff-summaries/javascript/relational-operator.json @@ -10,7 +10,7 @@ 1, 1 ], - "name": "relational-operator.js", + "filepath": "relational-operator.js", "end": [ 1, 6 @@ -27,9 +27,9 @@ "filePaths": [ "relational-operator.js" ], - "sha1": "088c27d2d4e2150bac4bff85c129df8d90a407c2", + "sha1": "1e45dd36b9764f567061c70acdd3cef498dc138a", "gitDir": "test/corpus/repos/javascript", - "sha2": "99896fdbbc5545bb0eee52c97120fa5150d94611" + "sha2": "7fc18c1b9070ac38c624eadfb7fd6dff293b4fa7" } ,{ "testCaseDescription": "javascript-relational-operator-replacement-insert-test", @@ -43,7 +43,7 @@ 1, 1 ], - "name": "relational-operator.js", + "filepath": "relational-operator.js", "end": [ 1, 7 @@ -60,7 +60,7 @@ 2, 1 ], - "name": "relational-operator.js", + "filepath": "relational-operator.js", "end": [ 2, 6 @@ -77,9 +77,9 @@ "filePaths": [ "relational-operator.js" ], - "sha1": "99896fdbbc5545bb0eee52c97120fa5150d94611", + "sha1": "7fc18c1b9070ac38c624eadfb7fd6dff293b4fa7", "gitDir": "test/corpus/repos/javascript", - "sha2": "bbd92da747e4f47fad4edaf1195dadc110d799b9" + "sha2": "0fbfdc1af2f1a7437260d2d410a5bb829e996157" } ,{ "testCaseDescription": "javascript-relational-operator-delete-insert-test", @@ -90,9 +90,9 @@ "filePaths": [ "relational-operator.js" ], - "sha1": "bbd92da747e4f47fad4edaf1195dadc110d799b9", + "sha1": "0fbfdc1af2f1a7437260d2d410a5bb829e996157", "gitDir": "test/corpus/repos/javascript", - "sha2": "d9d45f12405ddc916f2f65a1b13d36db0fc8985c" + "sha2": "f907b463a8abb29c798d611351aa1df72656c0c6" } ,{ "testCaseDescription": "javascript-relational-operator-replacement-test", @@ -103,9 +103,9 @@ "filePaths": [ "relational-operator.js" ], - "sha1": "d9d45f12405ddc916f2f65a1b13d36db0fc8985c", + "sha1": "f907b463a8abb29c798d611351aa1df72656c0c6", "gitDir": "test/corpus/repos/javascript", - "sha2": "341f8be98d72057a2d1736e13143bc898c9b8e93" + "sha2": "5b33c05fdfd0692ddcb9451bcaf6535f7a52df31" } ,{ "testCaseDescription": "javascript-relational-operator-delete-replacement-test", @@ -119,7 +119,7 @@ 1, 1 ], - "name": "relational-operator.js", + "filepath": "relational-operator.js", "end": [ 1, 7 @@ -136,9 +136,9 @@ "filePaths": [ "relational-operator.js" ], - "sha1": "341f8be98d72057a2d1736e13143bc898c9b8e93", + "sha1": "5b33c05fdfd0692ddcb9451bcaf6535f7a52df31", "gitDir": "test/corpus/repos/javascript", - "sha2": "9e5a228fb034020f7bc62fc7200a359f597cdb08" + "sha2": "17439ab331d062235bb16aed0354a7a21ae009b1" } ,{ "testCaseDescription": "javascript-relational-operator-delete-test", @@ -152,7 +152,7 @@ 1, 1 ], - "name": "relational-operator.js", + "filepath": "relational-operator.js", "end": [ 1, 6 @@ -169,9 +169,9 @@ "filePaths": [ "relational-operator.js" ], - "sha1": "9e5a228fb034020f7bc62fc7200a359f597cdb08", + "sha1": "17439ab331d062235bb16aed0354a7a21ae009b1", "gitDir": "test/corpus/repos/javascript", - "sha2": "8e766c6c2f81c0364155153280eb3508335180ce" + "sha2": "ddeb4dc93b5d0fe5acd72bb78a4a9ca94a109a75" } ,{ "testCaseDescription": "javascript-relational-operator-delete-rest-test", @@ -185,7 +185,7 @@ 1, 1 ], - "name": "relational-operator.js", + "filepath": "relational-operator.js", "end": [ 1, 7 @@ -202,7 +202,7 @@ "filePaths": [ "relational-operator.js" ], - "sha1": "8e766c6c2f81c0364155153280eb3508335180ce", + "sha1": "ddeb4dc93b5d0fe5acd72bb78a4a9ca94a109a75", "gitDir": "test/corpus/repos/javascript", - "sha2": "0f63f399f084244c4cfcd918876a8c5e659e8ade" + "sha2": "e9103bda916070cdf740003bec51e1082562c7c7" }] diff --git a/test/corpus/diff-summaries/javascript/return-statement.json b/test/corpus/diff-summaries/javascript/return-statement.json index 4235f50c6..f48c44c10 100644 --- a/test/corpus/diff-summaries/javascript/return-statement.json +++ b/test/corpus/diff-summaries/javascript/return-statement.json @@ -10,7 +10,7 @@ 1, 1 ], - "name": "return-statement.js", + "filepath": "return-statement.js", "end": [ 1, 10 @@ -27,9 +27,9 @@ "filePaths": [ "return-statement.js" ], - "sha1": "fd292d1b33fb3253b0d0f66bae29de22c247d85c", + "sha1": "daabccbd2883735c6857ab0915312ae394349add", "gitDir": "test/corpus/repos/javascript", - "sha2": "39c3556dd3f840127f75e3c79588e7f511f3bcd7" + "sha2": "9f8f004f4247b53b3789b2a56ff84c8d7a18176b" } ,{ "testCaseDescription": "javascript-return-statement-replacement-insert-test", @@ -43,7 +43,7 @@ 1, 1 ], - "name": "return-statement.js", + "filepath": "return-statement.js", "end": [ 1, 8 @@ -60,7 +60,7 @@ 2, 1 ], - "name": "return-statement.js", + "filepath": "return-statement.js", "end": [ 2, 10 @@ -77,9 +77,9 @@ "filePaths": [ "return-statement.js" ], - "sha1": "39c3556dd3f840127f75e3c79588e7f511f3bcd7", + "sha1": "9f8f004f4247b53b3789b2a56ff84c8d7a18176b", "gitDir": "test/corpus/repos/javascript", - "sha2": "06973c03af9ae606230fc06efbe7eeab89189937" + "sha2": "b6731e39dbbf0a0b8363d4692538c6d1a5cb09e0" } ,{ "testCaseDescription": "javascript-return-statement-delete-insert-test", @@ -93,7 +93,7 @@ 1, 8 ], - "name": "return-statement.js", + "filepath": "return-statement.js", "end": [ 1, 9 @@ -110,9 +110,9 @@ "filePaths": [ "return-statement.js" ], - "sha1": "06973c03af9ae606230fc06efbe7eeab89189937", + "sha1": "b6731e39dbbf0a0b8363d4692538c6d1a5cb09e0", "gitDir": "test/corpus/repos/javascript", - "sha2": "59a474f44f6019fa35db3ffeecbcd1b302aaf020" + "sha2": "9bcef2b9da40cac9680c1fb487ed036569580f92" } ,{ "testCaseDescription": "javascript-return-statement-replacement-test", @@ -126,7 +126,7 @@ 1, 8 ], - "name": "return-statement.js", + "filepath": "return-statement.js", "end": [ 1, 9 @@ -143,9 +143,9 @@ "filePaths": [ "return-statement.js" ], - "sha1": "59a474f44f6019fa35db3ffeecbcd1b302aaf020", + "sha1": "9bcef2b9da40cac9680c1fb487ed036569580f92", "gitDir": "test/corpus/repos/javascript", - "sha2": "cbd58b54a42ef7dbca45cb256da3aa7dd40bbf8f" + "sha2": "58752600312a74dc063f0bd8dd95556386349576" } ,{ "testCaseDescription": "javascript-return-statement-delete-replacement-test", @@ -159,7 +159,7 @@ 1, 1 ], - "name": "return-statement.js", + "filepath": "return-statement.js", "end": [ 1, 8 @@ -176,7 +176,7 @@ 2, 1 ], - "name": "return-statement.js", + "filepath": "return-statement.js", "end": [ 2, 10 @@ -193,7 +193,7 @@ 2, 1 ], - "name": "return-statement.js", + "filepath": "return-statement.js", "end": [ 2, 8 @@ -210,9 +210,9 @@ "filePaths": [ "return-statement.js" ], - "sha1": "cbd58b54a42ef7dbca45cb256da3aa7dd40bbf8f", + "sha1": "58752600312a74dc063f0bd8dd95556386349576", "gitDir": "test/corpus/repos/javascript", - "sha2": "dd13d4d79b349314a4b9bd2206ab12dbfbcc76b7" + "sha2": "9135caebc4d6189606a3536ff2ead5c01b41b30f" } ,{ "testCaseDescription": "javascript-return-statement-delete-test", @@ -226,7 +226,7 @@ 1, 1 ], - "name": "return-statement.js", + "filepath": "return-statement.js", "end": [ 1, 10 @@ -243,9 +243,9 @@ "filePaths": [ "return-statement.js" ], - "sha1": "dd13d4d79b349314a4b9bd2206ab12dbfbcc76b7", + "sha1": "9135caebc4d6189606a3536ff2ead5c01b41b30f", "gitDir": "test/corpus/repos/javascript", - "sha2": "79c2cb5f5a18808a2d8a5370443f65e371f589cb" + "sha2": "0693b986a990c398182028243b13801c4d7bfb09" } ,{ "testCaseDescription": "javascript-return-statement-delete-rest-test", @@ -259,7 +259,7 @@ 1, 1 ], - "name": "return-statement.js", + "filepath": "return-statement.js", "end": [ 1, 8 @@ -276,7 +276,7 @@ "filePaths": [ "return-statement.js" ], - "sha1": "79c2cb5f5a18808a2d8a5370443f65e371f589cb", + "sha1": "0693b986a990c398182028243b13801c4d7bfb09", "gitDir": "test/corpus/repos/javascript", - "sha2": "c97ecbdf25494ecedeff774f0dc2dc3e46859eb2" + "sha2": "707898c2c531fcefc9824bf46e51e45acd6c5fa8" }] diff --git a/test/corpus/diff-summaries/javascript/string.json b/test/corpus/diff-summaries/javascript/string.json index 9584a362d..b3e7f4570 100644 --- a/test/corpus/diff-summaries/javascript/string.json +++ b/test/corpus/diff-summaries/javascript/string.json @@ -10,7 +10,7 @@ 1, 1 ], - "name": "string.js", + "filepath": "string.js", "end": [ 1, 32 @@ -27,9 +27,9 @@ "filePaths": [ "string.js" ], - "sha1": "802ec5ac85b69eebd846079cc2cd500021a32d84", + "sha1": "9fc8725cb0db3098e8bec27b01f513b2994a3170", "gitDir": "test/corpus/repos/javascript", - "sha2": "548cff33fc83a827c59de7198e8c91370e15a032" + "sha2": "43d812174196e0d174524aa17aa64a28581caa0a" } ,{ "testCaseDescription": "javascript-string-replacement-insert-test", @@ -43,7 +43,7 @@ 1, 1 ], - "name": "string.js", + "filepath": "string.js", "end": [ 1, 42 @@ -60,7 +60,7 @@ 2, 1 ], - "name": "string.js", + "filepath": "string.js", "end": [ 2, 32 @@ -77,9 +77,9 @@ "filePaths": [ "string.js" ], - "sha1": "548cff33fc83a827c59de7198e8c91370e15a032", + "sha1": "43d812174196e0d174524aa17aa64a28581caa0a", "gitDir": "test/corpus/repos/javascript", - "sha2": "1374b4e8911a8aadedf8dd5e08ed34abeb631062" + "sha2": "97b2c06e7e6238dee71e96bdfc0fdc2f2e3c52d3" } ,{ "testCaseDescription": "javascript-string-delete-insert-test", @@ -94,7 +94,7 @@ 1, 1 ], - "name": "string.js", + "filepath": "string.js", "end": [ 1, 42 @@ -105,7 +105,7 @@ 1, 1 ], - "name": "string.js", + "filepath": "string.js", "end": [ 1, 32 @@ -123,9 +123,9 @@ "filePaths": [ "string.js" ], - "sha1": "1374b4e8911a8aadedf8dd5e08ed34abeb631062", + "sha1": "97b2c06e7e6238dee71e96bdfc0fdc2f2e3c52d3", "gitDir": "test/corpus/repos/javascript", - "sha2": "6d07e2009288c2a768cd297475105b5b41da7090" + "sha2": "115062ccaeaaea5d8590d56a76237d65f028e052" } ,{ "testCaseDescription": "javascript-string-replacement-test", @@ -140,7 +140,7 @@ 1, 1 ], - "name": "string.js", + "filepath": "string.js", "end": [ 1, 32 @@ -151,7 +151,7 @@ 1, 1 ], - "name": "string.js", + "filepath": "string.js", "end": [ 1, 42 @@ -169,9 +169,9 @@ "filePaths": [ "string.js" ], - "sha1": "6d07e2009288c2a768cd297475105b5b41da7090", + "sha1": "115062ccaeaaea5d8590d56a76237d65f028e052", "gitDir": "test/corpus/repos/javascript", - "sha2": "b87c05c3b0d2f211e6f9672c8d7d27b6c7572b58" + "sha2": "9621beac6b87e5ce2d189d6db1f35e3e172b4007" } ,{ "testCaseDescription": "javascript-string-delete-replacement-test", @@ -185,7 +185,7 @@ 1, 1 ], - "name": "string.js", + "filepath": "string.js", "end": [ 1, 42 @@ -202,7 +202,7 @@ 2, 1 ], - "name": "string.js", + "filepath": "string.js", "end": [ 2, 32 @@ -219,7 +219,7 @@ 2, 1 ], - "name": "string.js", + "filepath": "string.js", "end": [ 2, 42 @@ -236,9 +236,9 @@ "filePaths": [ "string.js" ], - "sha1": "b87c05c3b0d2f211e6f9672c8d7d27b6c7572b58", + "sha1": "9621beac6b87e5ce2d189d6db1f35e3e172b4007", "gitDir": "test/corpus/repos/javascript", - "sha2": "afbfb5f5d581d7a3a75d92c1ce2d8d4271889982" + "sha2": "615e5b92888945de9ce41fd3d0fde334ccaa5d33" } ,{ "testCaseDescription": "javascript-string-delete-test", @@ -252,7 +252,7 @@ 1, 1 ], - "name": "string.js", + "filepath": "string.js", "end": [ 1, 32 @@ -269,9 +269,9 @@ "filePaths": [ "string.js" ], - "sha1": "afbfb5f5d581d7a3a75d92c1ce2d8d4271889982", + "sha1": "615e5b92888945de9ce41fd3d0fde334ccaa5d33", "gitDir": "test/corpus/repos/javascript", - "sha2": "c78c48f8200e0c64c908a50aa9f96c73e69f27d8" + "sha2": "e9e5ca77c1c78b2974a5f6f44847ed361d4d8d7a" } ,{ "testCaseDescription": "javascript-string-delete-rest-test", @@ -285,7 +285,7 @@ 1, 1 ], - "name": "string.js", + "filepath": "string.js", "end": [ 1, 42 @@ -302,7 +302,7 @@ "filePaths": [ "string.js" ], - "sha1": "c78c48f8200e0c64c908a50aa9f96c73e69f27d8", + "sha1": "e9e5ca77c1c78b2974a5f6f44847ed361d4d8d7a", "gitDir": "test/corpus/repos/javascript", - "sha2": "c0f927bdea55b3ee78ee68522ae964808f19fab6" + "sha2": "ac1db4a743461368ea89c123db3cc0e26784eafd" }] diff --git a/test/corpus/diff-summaries/javascript/subscript-access-assignment.json b/test/corpus/diff-summaries/javascript/subscript-access-assignment.json index 68d55a251..632cd74af 100644 --- a/test/corpus/diff-summaries/javascript/subscript-access-assignment.json +++ b/test/corpus/diff-summaries/javascript/subscript-access-assignment.json @@ -10,7 +10,7 @@ 1, 1 ], - "name": "subscript-access-assignment.js", + "filepath": "subscript-access-assignment.js", "end": [ 1, 11 @@ -27,9 +27,9 @@ "filePaths": [ "subscript-access-assignment.js" ], - "sha1": "1e25a73e1015c39932d3a621daa9081a4e46a9ba", + "sha1": "76c3044c4a51bb3a3d9ac11057bd645a99531931", "gitDir": "test/corpus/repos/javascript", - "sha2": "feb25a87a8184064cf072dad1c33328049903fa8" + "sha2": "133880529a8a886fd17dfa2002af6e3314cf619e" } ,{ "testCaseDescription": "javascript-subscript-access-assignment-replacement-insert-test", @@ -43,7 +43,7 @@ 1, 1 ], - "name": "subscript-access-assignment.js", + "filepath": "subscript-access-assignment.js", "end": [ 1, 11 @@ -60,7 +60,7 @@ 2, 1 ], - "name": "subscript-access-assignment.js", + "filepath": "subscript-access-assignment.js", "end": [ 2, 11 @@ -77,9 +77,9 @@ "filePaths": [ "subscript-access-assignment.js" ], - "sha1": "feb25a87a8184064cf072dad1c33328049903fa8", + "sha1": "133880529a8a886fd17dfa2002af6e3314cf619e", "gitDir": "test/corpus/repos/javascript", - "sha2": "da4c6b87c8d120543ffd635714faa321f07480d0" + "sha2": "09a0625db2683ac0a081d394cc1a016266aa6caa" } ,{ "testCaseDescription": "javascript-subscript-access-assignment-delete-insert-test", @@ -94,7 +94,7 @@ 1, 10 ], - "name": "subscript-access-assignment.js", + "filepath": "subscript-access-assignment.js", "end": [ 1, 11 @@ -105,7 +105,7 @@ 1, 10 ], - "name": "subscript-access-assignment.js", + "filepath": "subscript-access-assignment.js", "end": [ 1, 11 @@ -123,9 +123,9 @@ "filePaths": [ "subscript-access-assignment.js" ], - "sha1": "da4c6b87c8d120543ffd635714faa321f07480d0", + "sha1": "09a0625db2683ac0a081d394cc1a016266aa6caa", "gitDir": "test/corpus/repos/javascript", - "sha2": "5661d8e351a9843d177881f6aa08f4c88396521f" + "sha2": "fed2e9a6540f863e45fbcc9e43d2ff0d6823cfa1" } ,{ "testCaseDescription": "javascript-subscript-access-assignment-replacement-test", @@ -140,7 +140,7 @@ 1, 10 ], - "name": "subscript-access-assignment.js", + "filepath": "subscript-access-assignment.js", "end": [ 1, 11 @@ -151,7 +151,7 @@ 1, 10 ], - "name": "subscript-access-assignment.js", + "filepath": "subscript-access-assignment.js", "end": [ 1, 11 @@ -169,9 +169,9 @@ "filePaths": [ "subscript-access-assignment.js" ], - "sha1": "5661d8e351a9843d177881f6aa08f4c88396521f", + "sha1": "fed2e9a6540f863e45fbcc9e43d2ff0d6823cfa1", "gitDir": "test/corpus/repos/javascript", - "sha2": "ab82b8ef3a5d6dcaed9da20dd7a3419f22819cba" + "sha2": "53f18bb523d53f0e37c551f9551fdf7d0d0df894" } ,{ "testCaseDescription": "javascript-subscript-access-assignment-delete-replacement-test", @@ -185,7 +185,7 @@ 1, 1 ], - "name": "subscript-access-assignment.js", + "filepath": "subscript-access-assignment.js", "end": [ 1, 11 @@ -202,7 +202,7 @@ 2, 1 ], - "name": "subscript-access-assignment.js", + "filepath": "subscript-access-assignment.js", "end": [ 2, 11 @@ -219,7 +219,7 @@ 2, 1 ], - "name": "subscript-access-assignment.js", + "filepath": "subscript-access-assignment.js", "end": [ 2, 11 @@ -236,9 +236,9 @@ "filePaths": [ "subscript-access-assignment.js" ], - "sha1": "ab82b8ef3a5d6dcaed9da20dd7a3419f22819cba", + "sha1": "53f18bb523d53f0e37c551f9551fdf7d0d0df894", "gitDir": "test/corpus/repos/javascript", - "sha2": "b6efb4049da7e27baf2a0d640a76e8ec471b348a" + "sha2": "e16d2224f4ca8089414ea4e64330375b69e4b45b" } ,{ "testCaseDescription": "javascript-subscript-access-assignment-delete-test", @@ -252,7 +252,7 @@ 1, 1 ], - "name": "subscript-access-assignment.js", + "filepath": "subscript-access-assignment.js", "end": [ 1, 11 @@ -269,9 +269,9 @@ "filePaths": [ "subscript-access-assignment.js" ], - "sha1": "b6efb4049da7e27baf2a0d640a76e8ec471b348a", + "sha1": "e16d2224f4ca8089414ea4e64330375b69e4b45b", "gitDir": "test/corpus/repos/javascript", - "sha2": "457674cd9d6b7c24f7eb6d98253aaa53783975e0" + "sha2": "409ca472403167d80dcbc1f9f1686581bcdbafc6" } ,{ "testCaseDescription": "javascript-subscript-access-assignment-delete-rest-test", @@ -285,7 +285,7 @@ 1, 1 ], - "name": "subscript-access-assignment.js", + "filepath": "subscript-access-assignment.js", "end": [ 1, 11 @@ -302,7 +302,7 @@ "filePaths": [ "subscript-access-assignment.js" ], - "sha1": "457674cd9d6b7c24f7eb6d98253aaa53783975e0", + "sha1": "409ca472403167d80dcbc1f9f1686581bcdbafc6", "gitDir": "test/corpus/repos/javascript", - "sha2": "462756b98c54f0b7551f56ee43c309cf51fd64a2" + "sha2": "ce44e2e8b8fa69e9c1d43bc9d72205e67352d30e" }] diff --git a/test/corpus/diff-summaries/javascript/subscript-access-string.json b/test/corpus/diff-summaries/javascript/subscript-access-string.json index 350e5a462..7fcd39370 100644 --- a/test/corpus/diff-summaries/javascript/subscript-access-string.json +++ b/test/corpus/diff-summaries/javascript/subscript-access-string.json @@ -10,7 +10,7 @@ 1, 1 ], - "name": "subscript-access-string.js", + "filepath": "subscript-access-string.js", "end": [ 1, 17 @@ -27,9 +27,9 @@ "filePaths": [ "subscript-access-string.js" ], - "sha1": "6157ae1cfd3503d356c628a06d397a81757e54f4", + "sha1": "cffeab56f3adf6806bb2776a0970bdf74e275881", "gitDir": "test/corpus/repos/javascript", - "sha2": "08e9034b9ef6e3217012295e66c7382e01880c99" + "sha2": "98d1de9f3cd177eaea064de5d29a705518cde93b" } ,{ "testCaseDescription": "javascript-subscript-access-string-replacement-insert-test", @@ -43,7 +43,7 @@ 1, 1 ], - "name": "subscript-access-string.js", + "filepath": "subscript-access-string.js", "end": [ 1, 23 @@ -60,7 +60,7 @@ 2, 1 ], - "name": "subscript-access-string.js", + "filepath": "subscript-access-string.js", "end": [ 2, 17 @@ -77,9 +77,9 @@ "filePaths": [ "subscript-access-string.js" ], - "sha1": "08e9034b9ef6e3217012295e66c7382e01880c99", + "sha1": "98d1de9f3cd177eaea064de5d29a705518cde93b", "gitDir": "test/corpus/repos/javascript", - "sha2": "81eedf476b04fde83921c08252fc8e7a2919d538" + "sha2": "95c340145d4f11bf19db967e44b300977865fc05" } ,{ "testCaseDescription": "javascript-subscript-access-string-delete-insert-test", @@ -94,7 +94,7 @@ 1, 3 ], - "name": "subscript-access-string.js", + "filepath": "subscript-access-string.js", "end": [ 1, 22 @@ -105,7 +105,7 @@ 1, 3 ], - "name": "subscript-access-string.js", + "filepath": "subscript-access-string.js", "end": [ 1, 16 @@ -123,9 +123,9 @@ "filePaths": [ "subscript-access-string.js" ], - "sha1": "81eedf476b04fde83921c08252fc8e7a2919d538", + "sha1": "95c340145d4f11bf19db967e44b300977865fc05", "gitDir": "test/corpus/repos/javascript", - "sha2": "5ae81906741dac99bbee475ab6f691d3f8e1d2f5" + "sha2": "b9afc33ce2b1a3aa7c4201c4af749d01c0dcbf61" } ,{ "testCaseDescription": "javascript-subscript-access-string-replacement-test", @@ -140,7 +140,7 @@ 1, 3 ], - "name": "subscript-access-string.js", + "filepath": "subscript-access-string.js", "end": [ 1, 16 @@ -151,7 +151,7 @@ 1, 3 ], - "name": "subscript-access-string.js", + "filepath": "subscript-access-string.js", "end": [ 1, 22 @@ -169,9 +169,9 @@ "filePaths": [ "subscript-access-string.js" ], - "sha1": "5ae81906741dac99bbee475ab6f691d3f8e1d2f5", + "sha1": "b9afc33ce2b1a3aa7c4201c4af749d01c0dcbf61", "gitDir": "test/corpus/repos/javascript", - "sha2": "782ec6465c6cbcb66f2c76656667cb580783e295" + "sha2": "04ac2b9be10ceb6278b57e20c8417de9d599a8d4" } ,{ "testCaseDescription": "javascript-subscript-access-string-delete-replacement-test", @@ -185,7 +185,7 @@ 1, 1 ], - "name": "subscript-access-string.js", + "filepath": "subscript-access-string.js", "end": [ 1, 23 @@ -202,7 +202,7 @@ 2, 1 ], - "name": "subscript-access-string.js", + "filepath": "subscript-access-string.js", "end": [ 2, 17 @@ -219,7 +219,7 @@ 2, 1 ], - "name": "subscript-access-string.js", + "filepath": "subscript-access-string.js", "end": [ 2, 23 @@ -236,9 +236,9 @@ "filePaths": [ "subscript-access-string.js" ], - "sha1": "782ec6465c6cbcb66f2c76656667cb580783e295", + "sha1": "04ac2b9be10ceb6278b57e20c8417de9d599a8d4", "gitDir": "test/corpus/repos/javascript", - "sha2": "8330dd9edc9588468c3f7d5ecd5361b4b8b069fc" + "sha2": "cc6020edb8965b0383b1e18218adb74e385ffa71" } ,{ "testCaseDescription": "javascript-subscript-access-string-delete-test", @@ -252,7 +252,7 @@ 1, 1 ], - "name": "subscript-access-string.js", + "filepath": "subscript-access-string.js", "end": [ 1, 17 @@ -269,9 +269,9 @@ "filePaths": [ "subscript-access-string.js" ], - "sha1": "8330dd9edc9588468c3f7d5ecd5361b4b8b069fc", + "sha1": "cc6020edb8965b0383b1e18218adb74e385ffa71", "gitDir": "test/corpus/repos/javascript", - "sha2": "2b39a76e2c82616a1bbe59de9ee12700e302a5bb" + "sha2": "509e2dbcaadbfb6d18ce4f46cd478a910955781d" } ,{ "testCaseDescription": "javascript-subscript-access-string-delete-rest-test", @@ -285,7 +285,7 @@ 1, 1 ], - "name": "subscript-access-string.js", + "filepath": "subscript-access-string.js", "end": [ 1, 23 @@ -302,7 +302,7 @@ "filePaths": [ "subscript-access-string.js" ], - "sha1": "2b39a76e2c82616a1bbe59de9ee12700e302a5bb", + "sha1": "509e2dbcaadbfb6d18ce4f46cd478a910955781d", "gitDir": "test/corpus/repos/javascript", - "sha2": "9dc1c8722d84e3f245688e90b8cf7155c95f446f" + "sha2": "9dc200c0d55a7794bef3c9006686c9d43b15c0fc" }] diff --git a/test/corpus/diff-summaries/javascript/subscript-access-variable.json b/test/corpus/diff-summaries/javascript/subscript-access-variable.json index d03fa8e22..da2d9d498 100644 --- a/test/corpus/diff-summaries/javascript/subscript-access-variable.json +++ b/test/corpus/diff-summaries/javascript/subscript-access-variable.json @@ -10,7 +10,7 @@ 1, 1 ], - "name": "subscript-access-variable.js", + "filepath": "subscript-access-variable.js", "end": [ 1, 16 @@ -27,9 +27,9 @@ "filePaths": [ "subscript-access-variable.js" ], - "sha1": "34a84c5fb21b25b173aca33ee72df362b955f3ee", + "sha1": "7ea7047c985acab4ba9cda1b937510a8c0d90974", "gitDir": "test/corpus/repos/javascript", - "sha2": "ccca96ceb275d35019acee7af10cec4dcb9c140e" + "sha2": "ee38cd908ad98061a3f3c1112ca450fe0e5a8be5" } ,{ "testCaseDescription": "javascript-subscript-access-variable-replacement-insert-test", @@ -43,7 +43,7 @@ 1, 1 ], - "name": "subscript-access-variable.js", + "filepath": "subscript-access-variable.js", "end": [ 1, 21 @@ -60,7 +60,7 @@ 2, 1 ], - "name": "subscript-access-variable.js", + "filepath": "subscript-access-variable.js", "end": [ 2, 16 @@ -77,9 +77,9 @@ "filePaths": [ "subscript-access-variable.js" ], - "sha1": "ccca96ceb275d35019acee7af10cec4dcb9c140e", + "sha1": "ee38cd908ad98061a3f3c1112ca450fe0e5a8be5", "gitDir": "test/corpus/repos/javascript", - "sha2": "14446e4157483ffafdd7e5ed66d7093ab0a6076b" + "sha2": "27460b9f4461575ce00fd4d3ebb2be5dc07dd06b" } ,{ "testCaseDescription": "javascript-subscript-access-variable-delete-insert-test", @@ -94,7 +94,7 @@ 1, 3 ], - "name": "subscript-access-variable.js", + "filepath": "subscript-access-variable.js", "end": [ 1, 20 @@ -105,7 +105,7 @@ 1, 3 ], - "name": "subscript-access-variable.js", + "filepath": "subscript-access-variable.js", "end": [ 1, 15 @@ -123,9 +123,9 @@ "filePaths": [ "subscript-access-variable.js" ], - "sha1": "14446e4157483ffafdd7e5ed66d7093ab0a6076b", + "sha1": "27460b9f4461575ce00fd4d3ebb2be5dc07dd06b", "gitDir": "test/corpus/repos/javascript", - "sha2": "1d98a4fb0a9300fc55f4533eb6f30e75e4a3be3b" + "sha2": "041dc95f0a1e2d63fdb37da60c69f98c177bca1c" } ,{ "testCaseDescription": "javascript-subscript-access-variable-replacement-test", @@ -140,7 +140,7 @@ 1, 3 ], - "name": "subscript-access-variable.js", + "filepath": "subscript-access-variable.js", "end": [ 1, 15 @@ -151,7 +151,7 @@ 1, 3 ], - "name": "subscript-access-variable.js", + "filepath": "subscript-access-variable.js", "end": [ 1, 20 @@ -169,9 +169,9 @@ "filePaths": [ "subscript-access-variable.js" ], - "sha1": "1d98a4fb0a9300fc55f4533eb6f30e75e4a3be3b", + "sha1": "041dc95f0a1e2d63fdb37da60c69f98c177bca1c", "gitDir": "test/corpus/repos/javascript", - "sha2": "4a34ec4c1e6412c882409c83c46b8d2612543cbd" + "sha2": "dfc758f05af136c934d1499ddef0e5035fd7f7ca" } ,{ "testCaseDescription": "javascript-subscript-access-variable-delete-replacement-test", @@ -185,7 +185,7 @@ 1, 1 ], - "name": "subscript-access-variable.js", + "filepath": "subscript-access-variable.js", "end": [ 1, 21 @@ -202,7 +202,7 @@ 2, 1 ], - "name": "subscript-access-variable.js", + "filepath": "subscript-access-variable.js", "end": [ 2, 16 @@ -219,7 +219,7 @@ 2, 1 ], - "name": "subscript-access-variable.js", + "filepath": "subscript-access-variable.js", "end": [ 2, 21 @@ -236,9 +236,9 @@ "filePaths": [ "subscript-access-variable.js" ], - "sha1": "4a34ec4c1e6412c882409c83c46b8d2612543cbd", + "sha1": "dfc758f05af136c934d1499ddef0e5035fd7f7ca", "gitDir": "test/corpus/repos/javascript", - "sha2": "cc7e39b323d13e1f410286e56d0fb0128950d715" + "sha2": "d14cc4640ea1cc84d49aadae6ad6eb93eea27e6b" } ,{ "testCaseDescription": "javascript-subscript-access-variable-delete-test", @@ -252,7 +252,7 @@ 1, 1 ], - "name": "subscript-access-variable.js", + "filepath": "subscript-access-variable.js", "end": [ 1, 16 @@ -269,9 +269,9 @@ "filePaths": [ "subscript-access-variable.js" ], - "sha1": "cc7e39b323d13e1f410286e56d0fb0128950d715", + "sha1": "d14cc4640ea1cc84d49aadae6ad6eb93eea27e6b", "gitDir": "test/corpus/repos/javascript", - "sha2": "f21d7b5aa1767f892bf1d76df7ade14f62d7e749" + "sha2": "8ce86e17b0f9b624ccc3658bfe392bc0d567b15f" } ,{ "testCaseDescription": "javascript-subscript-access-variable-delete-rest-test", @@ -285,7 +285,7 @@ 1, 1 ], - "name": "subscript-access-variable.js", + "filepath": "subscript-access-variable.js", "end": [ 1, 21 @@ -302,7 +302,7 @@ "filePaths": [ "subscript-access-variable.js" ], - "sha1": "f21d7b5aa1767f892bf1d76df7ade14f62d7e749", + "sha1": "8ce86e17b0f9b624ccc3658bfe392bc0d567b15f", "gitDir": "test/corpus/repos/javascript", - "sha2": "6157ae1cfd3503d356c628a06d397a81757e54f4" + "sha2": "f1bfa95a6741c9e2a6e9b3282dd511452c7a6882" }] diff --git a/test/corpus/diff-summaries/javascript/switch-statement.json b/test/corpus/diff-summaries/javascript/switch-statement.json index e19cd0ddf..8a69e21d1 100644 --- a/test/corpus/diff-summaries/javascript/switch-statement.json +++ b/test/corpus/diff-summaries/javascript/switch-statement.json @@ -10,7 +10,7 @@ 1, 1 ], - "name": "switch-statement.js", + "filepath": "switch-statement.js", "end": [ 1, 48 @@ -27,9 +27,9 @@ "filePaths": [ "switch-statement.js" ], - "sha1": "7d081d5591b64adba332f89a0a3aeba494aa1b0e", + "sha1": "e2a9bd90f6bdbd15c5b8a354953f27b8ea76dd9a", "gitDir": "test/corpus/repos/javascript", - "sha2": "810a8ba269ce2c084bdd064eb49b2f48e0d9a623" + "sha2": "df3c3be78ac29aa905f1440e9a2b9c25450a3550" } ,{ "testCaseDescription": "javascript-switch-statement-replacement-insert-test", @@ -43,7 +43,7 @@ 1, 1 ], - "name": "switch-statement.js", + "filepath": "switch-statement.js", "end": [ 1, 48 @@ -60,7 +60,7 @@ 2, 1 ], - "name": "switch-statement.js", + "filepath": "switch-statement.js", "end": [ 2, 48 @@ -77,9 +77,9 @@ "filePaths": [ "switch-statement.js" ], - "sha1": "810a8ba269ce2c084bdd064eb49b2f48e0d9a623", + "sha1": "df3c3be78ac29aa905f1440e9a2b9c25450a3550", "gitDir": "test/corpus/repos/javascript", - "sha2": "ab54c903bdfdd5daba8364e3500bc6c49b39be5c" + "sha2": "33e9d4f2a337a5555bea2dfe141b7bde76706286" } ,{ "testCaseDescription": "javascript-switch-statement-delete-insert-test", @@ -94,7 +94,7 @@ 1, 9 ], - "name": "switch-statement.js", + "filepath": "switch-statement.js", "end": [ 1, 10 @@ -105,7 +105,7 @@ 1, 9 ], - "name": "switch-statement.js", + "filepath": "switch-statement.js", "end": [ 1, 10 @@ -124,7 +124,7 @@ 1, 33 ], - "name": "switch-statement.js", + "filepath": "switch-statement.js", "end": [ 1, 34 @@ -135,7 +135,7 @@ 1, 33 ], - "name": "switch-statement.js", + "filepath": "switch-statement.js", "end": [ 1, 34 @@ -153,9 +153,9 @@ "filePaths": [ "switch-statement.js" ], - "sha1": "ab54c903bdfdd5daba8364e3500bc6c49b39be5c", + "sha1": "33e9d4f2a337a5555bea2dfe141b7bde76706286", "gitDir": "test/corpus/repos/javascript", - "sha2": "5739e34c49d07d0c4f4796d50bc226e410898aa5" + "sha2": "506fcdd7fd3b630a3f017d87247caca79e4f1e41" } ,{ "testCaseDescription": "javascript-switch-statement-replacement-test", @@ -170,7 +170,7 @@ 1, 9 ], - "name": "switch-statement.js", + "filepath": "switch-statement.js", "end": [ 1, 10 @@ -181,7 +181,7 @@ 1, 9 ], - "name": "switch-statement.js", + "filepath": "switch-statement.js", "end": [ 1, 10 @@ -200,7 +200,7 @@ 1, 33 ], - "name": "switch-statement.js", + "filepath": "switch-statement.js", "end": [ 1, 34 @@ -211,7 +211,7 @@ 1, 33 ], - "name": "switch-statement.js", + "filepath": "switch-statement.js", "end": [ 1, 34 @@ -229,9 +229,9 @@ "filePaths": [ "switch-statement.js" ], - "sha1": "5739e34c49d07d0c4f4796d50bc226e410898aa5", + "sha1": "506fcdd7fd3b630a3f017d87247caca79e4f1e41", "gitDir": "test/corpus/repos/javascript", - "sha2": "5ede9d3d51ac8a5d2b5b82baca9ee75cdca1dd00" + "sha2": "52687fb608acb2914550ed85deaa27582380bec4" } ,{ "testCaseDescription": "javascript-switch-statement-delete-replacement-test", @@ -245,7 +245,7 @@ 1, 1 ], - "name": "switch-statement.js", + "filepath": "switch-statement.js", "end": [ 1, 48 @@ -262,7 +262,7 @@ 2, 1 ], - "name": "switch-statement.js", + "filepath": "switch-statement.js", "end": [ 2, 48 @@ -279,7 +279,7 @@ 2, 1 ], - "name": "switch-statement.js", + "filepath": "switch-statement.js", "end": [ 2, 48 @@ -296,9 +296,9 @@ "filePaths": [ "switch-statement.js" ], - "sha1": "5ede9d3d51ac8a5d2b5b82baca9ee75cdca1dd00", + "sha1": "52687fb608acb2914550ed85deaa27582380bec4", "gitDir": "test/corpus/repos/javascript", - "sha2": "d156d794fda50ada98b7825eebd0f3e420785a6b" + "sha2": "cde751ef7a519c64c0060699db2c1c8766256b81" } ,{ "testCaseDescription": "javascript-switch-statement-delete-test", @@ -312,7 +312,7 @@ 1, 1 ], - "name": "switch-statement.js", + "filepath": "switch-statement.js", "end": [ 1, 48 @@ -329,9 +329,9 @@ "filePaths": [ "switch-statement.js" ], - "sha1": "d156d794fda50ada98b7825eebd0f3e420785a6b", + "sha1": "cde751ef7a519c64c0060699db2c1c8766256b81", "gitDir": "test/corpus/repos/javascript", - "sha2": "9fa78cd32cd480820b95fbb40ea837dae8d98019" + "sha2": "7ad46fe9d54b3b84d57d387e72f13777834a0c04" } ,{ "testCaseDescription": "javascript-switch-statement-delete-rest-test", @@ -345,7 +345,7 @@ 1, 1 ], - "name": "switch-statement.js", + "filepath": "switch-statement.js", "end": [ 1, 48 @@ -362,7 +362,7 @@ "filePaths": [ "switch-statement.js" ], - "sha1": "9fa78cd32cd480820b95fbb40ea837dae8d98019", + "sha1": "7ad46fe9d54b3b84d57d387e72f13777834a0c04", "gitDir": "test/corpus/repos/javascript", - "sha2": "d3cabdc9dab4bc3c11777bbc5a792d76b819c732" + "sha2": "002bab7c41e8650a1bd8d725e583ee98e187b92a" }] diff --git a/test/corpus/diff-summaries/javascript/template-string.json b/test/corpus/diff-summaries/javascript/template-string.json index 7816ccad1..5da4fea33 100644 --- a/test/corpus/diff-summaries/javascript/template-string.json +++ b/test/corpus/diff-summaries/javascript/template-string.json @@ -10,7 +10,7 @@ 1, 1 ], - "name": "template-string.js", + "filepath": "template-string.js", "end": [ 1, 11 @@ -27,9 +27,9 @@ "filePaths": [ "template-string.js" ], - "sha1": "b2046cbd2baf7870677913d1acc35696f7a97f84", + "sha1": "bfc370655107d017eac50a03912e0145b75f9a64", "gitDir": "test/corpus/repos/javascript", - "sha2": "86eea3a9c43e1c8981341e2d81fdb8b21ef67e38" + "sha2": "56779813370db736ffdb93aed6c1ec9cb26b62e3" } ,{ "testCaseDescription": "javascript-template-string-replacement-insert-test", @@ -43,7 +43,7 @@ 1, 1 ], - "name": "template-string.js", + "filepath": "template-string.js", "end": [ 1, 13 @@ -60,7 +60,7 @@ 2, 1 ], - "name": "template-string.js", + "filepath": "template-string.js", "end": [ 2, 11 @@ -77,9 +77,9 @@ "filePaths": [ "template-string.js" ], - "sha1": "86eea3a9c43e1c8981341e2d81fdb8b21ef67e38", + "sha1": "56779813370db736ffdb93aed6c1ec9cb26b62e3", "gitDir": "test/corpus/repos/javascript", - "sha2": "cd8c59b544053f3b2b9e11384660f27ee3060ec8" + "sha2": "3e1add2cdaacd5599d6bb1896e16412c1d6eea64" } ,{ "testCaseDescription": "javascript-template-string-delete-insert-test", @@ -94,7 +94,7 @@ 1, 1 ], - "name": "template-string.js", + "filepath": "template-string.js", "end": [ 1, 13 @@ -105,7 +105,7 @@ 1, 1 ], - "name": "template-string.js", + "filepath": "template-string.js", "end": [ 1, 11 @@ -123,9 +123,9 @@ "filePaths": [ "template-string.js" ], - "sha1": "cd8c59b544053f3b2b9e11384660f27ee3060ec8", + "sha1": "3e1add2cdaacd5599d6bb1896e16412c1d6eea64", "gitDir": "test/corpus/repos/javascript", - "sha2": "212a15e06fdc26f0dd40b668e1e6c95888476a84" + "sha2": "f953f36fb6a3dd82722b97aec27bc7026490e863" } ,{ "testCaseDescription": "javascript-template-string-replacement-test", @@ -140,7 +140,7 @@ 1, 1 ], - "name": "template-string.js", + "filepath": "template-string.js", "end": [ 1, 11 @@ -151,7 +151,7 @@ 1, 1 ], - "name": "template-string.js", + "filepath": "template-string.js", "end": [ 1, 13 @@ -169,9 +169,9 @@ "filePaths": [ "template-string.js" ], - "sha1": "212a15e06fdc26f0dd40b668e1e6c95888476a84", + "sha1": "f953f36fb6a3dd82722b97aec27bc7026490e863", "gitDir": "test/corpus/repos/javascript", - "sha2": "16a3b8a4889116cd87e1421ca5336dc2512a9f71" + "sha2": "bbf4abacff1ced15c2d9f2a6eb88455c5af132b5" } ,{ "testCaseDescription": "javascript-template-string-delete-replacement-test", @@ -185,7 +185,7 @@ 1, 1 ], - "name": "template-string.js", + "filepath": "template-string.js", "end": [ 1, 13 @@ -202,7 +202,7 @@ 2, 1 ], - "name": "template-string.js", + "filepath": "template-string.js", "end": [ 2, 11 @@ -219,7 +219,7 @@ 2, 1 ], - "name": "template-string.js", + "filepath": "template-string.js", "end": [ 2, 13 @@ -236,9 +236,9 @@ "filePaths": [ "template-string.js" ], - "sha1": "16a3b8a4889116cd87e1421ca5336dc2512a9f71", + "sha1": "bbf4abacff1ced15c2d9f2a6eb88455c5af132b5", "gitDir": "test/corpus/repos/javascript", - "sha2": "da33d916e0e5bb8f980a2225a65c9518e0a347e8" + "sha2": "07edbeb37cad6b0f42d65587e0c4f1bd665de8d3" } ,{ "testCaseDescription": "javascript-template-string-delete-test", @@ -252,7 +252,7 @@ 1, 1 ], - "name": "template-string.js", + "filepath": "template-string.js", "end": [ 1, 11 @@ -269,9 +269,9 @@ "filePaths": [ "template-string.js" ], - "sha1": "da33d916e0e5bb8f980a2225a65c9518e0a347e8", + "sha1": "07edbeb37cad6b0f42d65587e0c4f1bd665de8d3", "gitDir": "test/corpus/repos/javascript", - "sha2": "67b51d8f3b174b011fc32cf8cba64246d727a44d" + "sha2": "e444cbce9bd6e5f403090a1b521390ad7ae88602" } ,{ "testCaseDescription": "javascript-template-string-delete-rest-test", @@ -285,7 +285,7 @@ 1, 1 ], - "name": "template-string.js", + "filepath": "template-string.js", "end": [ 1, 13 @@ -302,7 +302,7 @@ "filePaths": [ "template-string.js" ], - "sha1": "67b51d8f3b174b011fc32cf8cba64246d727a44d", + "sha1": "e444cbce9bd6e5f403090a1b521390ad7ae88602", "gitDir": "test/corpus/repos/javascript", - "sha2": "7fe4e0b214260f0482129909a00b5146e3bfc1da" + "sha2": "2edf2696e3ec6a0585d8129754cb7bcd3ce826d5" }] diff --git a/test/corpus/diff-summaries/javascript/ternary.json b/test/corpus/diff-summaries/javascript/ternary.json index 243dc8456..d44d2b266 100644 --- a/test/corpus/diff-summaries/javascript/ternary.json +++ b/test/corpus/diff-summaries/javascript/ternary.json @@ -10,7 +10,7 @@ 1, 1 ], - "name": "ternary.js", + "filepath": "ternary.js", "end": [ 1, 26 @@ -27,9 +27,9 @@ "filePaths": [ "ternary.js" ], - "sha1": "e9872de5faf687bc02c8b7a06031ef152b2d3dbe", + "sha1": "132c3dc38119abe623c8c7dbe1b5b26b4fa2c8fb", "gitDir": "test/corpus/repos/javascript", - "sha2": "d725fe936a6d1727eaaa36abf04dfafcf371ea56" + "sha2": "92b20d38000d4385ad48dd4c65f9fae203c4f9ae" } ,{ "testCaseDescription": "javascript-ternary-replacement-insert-test", @@ -43,7 +43,7 @@ 1, 1 ], - "name": "ternary.js", + "filepath": "ternary.js", "end": [ 1, 51 @@ -60,7 +60,7 @@ 2, 1 ], - "name": "ternary.js", + "filepath": "ternary.js", "end": [ 2, 26 @@ -77,9 +77,9 @@ "filePaths": [ "ternary.js" ], - "sha1": "d725fe936a6d1727eaaa36abf04dfafcf371ea56", + "sha1": "92b20d38000d4385ad48dd4c65f9fae203c4f9ae", "gitDir": "test/corpus/repos/javascript", - "sha2": "07fff336cbadcbc5323857dccba4368d79c29bfa" + "sha2": "9ff227c388c117d4a990ed65484cb9266381c13a" } ,{ "testCaseDescription": "javascript-ternary-delete-insert-test", @@ -93,7 +93,7 @@ 1, 1 ], - "name": "ternary.js", + "filepath": "ternary.js", "end": [ 1, 26 @@ -110,7 +110,7 @@ 1, 1 ], - "name": "ternary.js", + "filepath": "ternary.js", "end": [ 1, 51 @@ -127,9 +127,9 @@ "filePaths": [ "ternary.js" ], - "sha1": "07fff336cbadcbc5323857dccba4368d79c29bfa", + "sha1": "9ff227c388c117d4a990ed65484cb9266381c13a", "gitDir": "test/corpus/repos/javascript", - "sha2": "fde4df86574e034afb0c93f8bd4a0d5d0c0f4b93" + "sha2": "964dd33f73c5514f8b9f833c80f32530acc95d42" } ,{ "testCaseDescription": "javascript-ternary-replacement-test", @@ -143,7 +143,7 @@ 1, 1 ], - "name": "ternary.js", + "filepath": "ternary.js", "end": [ 1, 51 @@ -160,7 +160,7 @@ 1, 1 ], - "name": "ternary.js", + "filepath": "ternary.js", "end": [ 1, 26 @@ -177,9 +177,9 @@ "filePaths": [ "ternary.js" ], - "sha1": "fde4df86574e034afb0c93f8bd4a0d5d0c0f4b93", + "sha1": "964dd33f73c5514f8b9f833c80f32530acc95d42", "gitDir": "test/corpus/repos/javascript", - "sha2": "4e2cccf815c304ee0fbb9bb5c30aa7ed47545f31" + "sha2": "0d3ae604a18a26e2359aa6b23cfe421dbf897d57" } ,{ "testCaseDescription": "javascript-ternary-delete-replacement-test", @@ -193,7 +193,7 @@ 1, 1 ], - "name": "ternary.js", + "filepath": "ternary.js", "end": [ 1, 51 @@ -210,7 +210,7 @@ 2, 1 ], - "name": "ternary.js", + "filepath": "ternary.js", "end": [ 2, 26 @@ -227,7 +227,7 @@ 2, 1 ], - "name": "ternary.js", + "filepath": "ternary.js", "end": [ 2, 51 @@ -244,9 +244,9 @@ "filePaths": [ "ternary.js" ], - "sha1": "4e2cccf815c304ee0fbb9bb5c30aa7ed47545f31", + "sha1": "0d3ae604a18a26e2359aa6b23cfe421dbf897d57", "gitDir": "test/corpus/repos/javascript", - "sha2": "5902d16d5099cee6b0832454d00c60cf17df43f2" + "sha2": "e44b062896ec039b2e193fa2cd10049bae720322" } ,{ "testCaseDescription": "javascript-ternary-delete-test", @@ -260,7 +260,7 @@ 1, 1 ], - "name": "ternary.js", + "filepath": "ternary.js", "end": [ 1, 26 @@ -277,9 +277,9 @@ "filePaths": [ "ternary.js" ], - "sha1": "5902d16d5099cee6b0832454d00c60cf17df43f2", + "sha1": "e44b062896ec039b2e193fa2cd10049bae720322", "gitDir": "test/corpus/repos/javascript", - "sha2": "44fceb27d8f475cff6d431001462c36fa95522f2" + "sha2": "c35b9b86731f710c48d69bd798ec358a9053bde9" } ,{ "testCaseDescription": "javascript-ternary-delete-rest-test", @@ -293,7 +293,7 @@ 1, 1 ], - "name": "ternary.js", + "filepath": "ternary.js", "end": [ 1, 51 @@ -310,7 +310,7 @@ "filePaths": [ "ternary.js" ], - "sha1": "44fceb27d8f475cff6d431001462c36fa95522f2", + "sha1": "c35b9b86731f710c48d69bd798ec358a9053bde9", "gitDir": "test/corpus/repos/javascript", - "sha2": "3da268bcc8f3c57c756ab27cc04835366de458ed" + "sha2": "31738f50a638a8859e18abb4941175e584dec358" }] diff --git a/test/corpus/diff-summaries/javascript/this-expression.json b/test/corpus/diff-summaries/javascript/this-expression.json index cc554d20b..66eadbb73 100644 --- a/test/corpus/diff-summaries/javascript/this-expression.json +++ b/test/corpus/diff-summaries/javascript/this-expression.json @@ -10,7 +10,7 @@ 1, 1 ], - "name": "this-expression.js", + "filepath": "this-expression.js", "end": [ 1, 5 @@ -27,9 +27,9 @@ "filePaths": [ "this-expression.js" ], - "sha1": "562fd7786138fba4253581a1f2995c02007f74b9", + "sha1": "e9e97ee7989ab55b949be6baf66613ce0585a9a1", "gitDir": "test/corpus/repos/javascript", - "sha2": "8249b4041355beb537fdb71650db090530dec8ef" + "sha2": "b6934d1dff83b9373c5a06dd6e1b9b3b307af4c0" } ,{ "testCaseDescription": "javascript-this-expression-replacement-insert-test", @@ -43,7 +43,7 @@ 1, 1 ], - "name": "this-expression.js", + "filepath": "this-expression.js", "end": [ 1, 13 @@ -60,7 +60,7 @@ 2, 1 ], - "name": "this-expression.js", + "filepath": "this-expression.js", "end": [ 2, 5 @@ -77,9 +77,9 @@ "filePaths": [ "this-expression.js" ], - "sha1": "8249b4041355beb537fdb71650db090530dec8ef", + "sha1": "b6934d1dff83b9373c5a06dd6e1b9b3b307af4c0", "gitDir": "test/corpus/repos/javascript", - "sha2": "33067c8b424eb4ea275b613abdaae3c582423096" + "sha2": "e06d2f6d42d2a8a8ef850fc1e7dadf48fbf46a6e" } ,{ "testCaseDescription": "javascript-this-expression-delete-insert-test", @@ -93,7 +93,7 @@ 1, 1 ], - "name": "this-expression.js", + "filepath": "this-expression.js", "end": [ 1, 5 @@ -110,7 +110,7 @@ 1, 1 ], - "name": "this-expression.js", + "filepath": "this-expression.js", "end": [ 1, 13 @@ -127,9 +127,9 @@ "filePaths": [ "this-expression.js" ], - "sha1": "33067c8b424eb4ea275b613abdaae3c582423096", + "sha1": "e06d2f6d42d2a8a8ef850fc1e7dadf48fbf46a6e", "gitDir": "test/corpus/repos/javascript", - "sha2": "a9b3d6d799f7fae56377bdd4f6a5ccc8d5f8f2bf" + "sha2": "e31445499886dabdac48604d199ae92d8be138dd" } ,{ "testCaseDescription": "javascript-this-expression-replacement-test", @@ -143,7 +143,7 @@ 1, 1 ], - "name": "this-expression.js", + "filepath": "this-expression.js", "end": [ 1, 13 @@ -160,7 +160,7 @@ 1, 1 ], - "name": "this-expression.js", + "filepath": "this-expression.js", "end": [ 1, 5 @@ -177,9 +177,9 @@ "filePaths": [ "this-expression.js" ], - "sha1": "a9b3d6d799f7fae56377bdd4f6a5ccc8d5f8f2bf", + "sha1": "e31445499886dabdac48604d199ae92d8be138dd", "gitDir": "test/corpus/repos/javascript", - "sha2": "246370a44fa4b872413f05c128c04d672eae58fd" + "sha2": "0f9b242f71c86f20152c55e5bc23295084c4803c" } ,{ "testCaseDescription": "javascript-this-expression-delete-replacement-test", @@ -193,7 +193,7 @@ 1, 1 ], - "name": "this-expression.js", + "filepath": "this-expression.js", "end": [ 1, 13 @@ -210,7 +210,7 @@ 2, 1 ], - "name": "this-expression.js", + "filepath": "this-expression.js", "end": [ 2, 5 @@ -227,7 +227,7 @@ 2, 1 ], - "name": "this-expression.js", + "filepath": "this-expression.js", "end": [ 2, 13 @@ -244,9 +244,9 @@ "filePaths": [ "this-expression.js" ], - "sha1": "246370a44fa4b872413f05c128c04d672eae58fd", + "sha1": "0f9b242f71c86f20152c55e5bc23295084c4803c", "gitDir": "test/corpus/repos/javascript", - "sha2": "0737c39985667a5e266f35daa5baf2a07a394ad7" + "sha2": "1201e4aab1d090c7dcf73af5f6fbbd4fc430bade" } ,{ "testCaseDescription": "javascript-this-expression-delete-test", @@ -260,7 +260,7 @@ 1, 1 ], - "name": "this-expression.js", + "filepath": "this-expression.js", "end": [ 1, 5 @@ -277,9 +277,9 @@ "filePaths": [ "this-expression.js" ], - "sha1": "0737c39985667a5e266f35daa5baf2a07a394ad7", + "sha1": "1201e4aab1d090c7dcf73af5f6fbbd4fc430bade", "gitDir": "test/corpus/repos/javascript", - "sha2": "4ec6bdcaa9c02dc5d015c368f739cb0fa10f22d9" + "sha2": "a0f3d072a7cd5683a4fd04f54ff92233ffdd258d" } ,{ "testCaseDescription": "javascript-this-expression-delete-rest-test", @@ -293,7 +293,7 @@ 1, 1 ], - "name": "this-expression.js", + "filepath": "this-expression.js", "end": [ 1, 13 @@ -310,7 +310,7 @@ "filePaths": [ "this-expression.js" ], - "sha1": "4ec6bdcaa9c02dc5d015c368f739cb0fa10f22d9", + "sha1": "a0f3d072a7cd5683a4fd04f54ff92233ffdd258d", "gitDir": "test/corpus/repos/javascript", - "sha2": "71b405a91807f07e6c1c55a71a93c78d07b0b4ab" + "sha2": "91510d6ffae780e8110c34260022de5c4689306f" }] diff --git a/test/corpus/diff-summaries/javascript/throw-statement.json b/test/corpus/diff-summaries/javascript/throw-statement.json index 1b3a98d03..ef4ef76eb 100644 --- a/test/corpus/diff-summaries/javascript/throw-statement.json +++ b/test/corpus/diff-summaries/javascript/throw-statement.json @@ -10,7 +10,7 @@ 1, 1 ], - "name": "throw-statement.js", + "filepath": "throw-statement.js", "end": [ 1, 26 @@ -27,9 +27,9 @@ "filePaths": [ "throw-statement.js" ], - "sha1": "d3cabdc9dab4bc3c11777bbc5a792d76b819c732", + "sha1": "78353c22774683c0b59f51b4f54cdc3797a7a3ee", "gitDir": "test/corpus/repos/javascript", - "sha2": "e81a468723aa03296599372e20ecc7c1251ef654" + "sha2": "902803b6ab173f44f36a5167327252bf035245ef" } ,{ "testCaseDescription": "javascript-throw-statement-replacement-insert-test", @@ -43,7 +43,7 @@ 1, 1 ], - "name": "throw-statement.js", + "filepath": "throw-statement.js", "end": [ 1, 29 @@ -60,7 +60,7 @@ 2, 1 ], - "name": "throw-statement.js", + "filepath": "throw-statement.js", "end": [ 2, 26 @@ -77,9 +77,9 @@ "filePaths": [ "throw-statement.js" ], - "sha1": "e81a468723aa03296599372e20ecc7c1251ef654", + "sha1": "902803b6ab173f44f36a5167327252bf035245ef", "gitDir": "test/corpus/repos/javascript", - "sha2": "2a03554ea9e30a920d4fcdbec54c60cba731bb3d" + "sha2": "d2c11c5fa2567c7d3704f913cd7c7e33793a82e0" } ,{ "testCaseDescription": "javascript-throw-statement-delete-insert-test", @@ -94,7 +94,7 @@ 1, 17 ], - "name": "throw-statement.js", + "filepath": "throw-statement.js", "end": [ 1, 27 @@ -105,7 +105,7 @@ 1, 17 ], - "name": "throw-statement.js", + "filepath": "throw-statement.js", "end": [ 1, 24 @@ -123,9 +123,9 @@ "filePaths": [ "throw-statement.js" ], - "sha1": "2a03554ea9e30a920d4fcdbec54c60cba731bb3d", + "sha1": "d2c11c5fa2567c7d3704f913cd7c7e33793a82e0", "gitDir": "test/corpus/repos/javascript", - "sha2": "206657eed174831f61ce3147f00df2b8ba4c90f3" + "sha2": "b3f59095c9e211cf78fdbda36c096723f37cca3e" } ,{ "testCaseDescription": "javascript-throw-statement-replacement-test", @@ -140,7 +140,7 @@ 1, 17 ], - "name": "throw-statement.js", + "filepath": "throw-statement.js", "end": [ 1, 24 @@ -151,7 +151,7 @@ 1, 17 ], - "name": "throw-statement.js", + "filepath": "throw-statement.js", "end": [ 1, 27 @@ -169,9 +169,9 @@ "filePaths": [ "throw-statement.js" ], - "sha1": "206657eed174831f61ce3147f00df2b8ba4c90f3", + "sha1": "b3f59095c9e211cf78fdbda36c096723f37cca3e", "gitDir": "test/corpus/repos/javascript", - "sha2": "1e5ba14bad6d93d8db35db604e0c07b79bf4bb87" + "sha2": "82f33ecda3aade742e98b8119d99648e07845c26" } ,{ "testCaseDescription": "javascript-throw-statement-delete-replacement-test", @@ -185,7 +185,7 @@ 1, 1 ], - "name": "throw-statement.js", + "filepath": "throw-statement.js", "end": [ 1, 29 @@ -202,7 +202,7 @@ 2, 1 ], - "name": "throw-statement.js", + "filepath": "throw-statement.js", "end": [ 2, 26 @@ -219,7 +219,7 @@ 2, 1 ], - "name": "throw-statement.js", + "filepath": "throw-statement.js", "end": [ 2, 29 @@ -236,9 +236,9 @@ "filePaths": [ "throw-statement.js" ], - "sha1": "1e5ba14bad6d93d8db35db604e0c07b79bf4bb87", + "sha1": "82f33ecda3aade742e98b8119d99648e07845c26", "gitDir": "test/corpus/repos/javascript", - "sha2": "c3c3aa05ccd4314717771fa3cfcd116521c4e206" + "sha2": "51663869b27e8a07ccda353b957356a7614db361" } ,{ "testCaseDescription": "javascript-throw-statement-delete-test", @@ -252,7 +252,7 @@ 1, 1 ], - "name": "throw-statement.js", + "filepath": "throw-statement.js", "end": [ 1, 26 @@ -269,9 +269,9 @@ "filePaths": [ "throw-statement.js" ], - "sha1": "c3c3aa05ccd4314717771fa3cfcd116521c4e206", + "sha1": "51663869b27e8a07ccda353b957356a7614db361", "gitDir": "test/corpus/repos/javascript", - "sha2": "2a0fa3df9551511efb25e81d813ddb86a843cddf" + "sha2": "a92c6ff1eab17272e1d7b9f579d2ac77759433b7" } ,{ "testCaseDescription": "javascript-throw-statement-delete-rest-test", @@ -285,7 +285,7 @@ 1, 1 ], - "name": "throw-statement.js", + "filepath": "throw-statement.js", "end": [ 1, 29 @@ -302,7 +302,7 @@ "filePaths": [ "throw-statement.js" ], - "sha1": "2a0fa3df9551511efb25e81d813ddb86a843cddf", + "sha1": "a92c6ff1eab17272e1d7b9f579d2ac77759433b7", "gitDir": "test/corpus/repos/javascript", - "sha2": "37116a9b6cbef2a356805bbeaf6ab65cdcac7749" + "sha2": "9ea42ee5607e5b8128a9bda56be262d8a62b1639" }] diff --git a/test/corpus/diff-summaries/javascript/true.json b/test/corpus/diff-summaries/javascript/true.json index 420d31512..dbf6d01a1 100644 --- a/test/corpus/diff-summaries/javascript/true.json +++ b/test/corpus/diff-summaries/javascript/true.json @@ -10,7 +10,7 @@ 1, 1 ], - "name": "true.js", + "filepath": "true.js", "end": [ 1, 5 @@ -27,9 +27,9 @@ "filePaths": [ "true.js" ], - "sha1": "33c5c1f9cf953a752cbffb621c3f049a1da56ef6", + "sha1": "6e5ff43b1afae6cdf404ae5541d1cebb71974ed4", "gitDir": "test/corpus/repos/javascript", - "sha2": "a6ced4af62125992db2e4d0bf35e64a1ac2edec9" + "sha2": "1307d15440fa6d4dd856e699f1f622d81cc458b7" } ,{ "testCaseDescription": "javascript-true-replacement-insert-test", @@ -43,7 +43,7 @@ 1, 1 ], - "name": "true.js", + "filepath": "true.js", "end": [ 1, 13 @@ -60,7 +60,7 @@ 2, 1 ], - "name": "true.js", + "filepath": "true.js", "end": [ 2, 5 @@ -77,9 +77,9 @@ "filePaths": [ "true.js" ], - "sha1": "a6ced4af62125992db2e4d0bf35e64a1ac2edec9", + "sha1": "1307d15440fa6d4dd856e699f1f622d81cc458b7", "gitDir": "test/corpus/repos/javascript", - "sha2": "67c9f34040f63e7c6665a72b86ed606060accbad" + "sha2": "2fba2ffbf87727b963767962ffc08ca0833a0b9b" } ,{ "testCaseDescription": "javascript-true-delete-insert-test", @@ -93,7 +93,7 @@ 1, 1 ], - "name": "true.js", + "filepath": "true.js", "end": [ 1, 5 @@ -110,7 +110,7 @@ 1, 1 ], - "name": "true.js", + "filepath": "true.js", "end": [ 1, 13 @@ -127,9 +127,9 @@ "filePaths": [ "true.js" ], - "sha1": "67c9f34040f63e7c6665a72b86ed606060accbad", + "sha1": "2fba2ffbf87727b963767962ffc08ca0833a0b9b", "gitDir": "test/corpus/repos/javascript", - "sha2": "67f2af6013b86b0ba91f58ea0bb156ab8fef63d9" + "sha2": "5bcf27a7d59100e290749764b879c34588c9f026" } ,{ "testCaseDescription": "javascript-true-replacement-test", @@ -143,7 +143,7 @@ 1, 1 ], - "name": "true.js", + "filepath": "true.js", "end": [ 1, 13 @@ -160,7 +160,7 @@ 1, 1 ], - "name": "true.js", + "filepath": "true.js", "end": [ 1, 5 @@ -177,9 +177,9 @@ "filePaths": [ "true.js" ], - "sha1": "67f2af6013b86b0ba91f58ea0bb156ab8fef63d9", + "sha1": "5bcf27a7d59100e290749764b879c34588c9f026", "gitDir": "test/corpus/repos/javascript", - "sha2": "20e525bfe23a51c65b7fb2ab38d615b8b79158de" + "sha2": "e9fecdea0ced5209f1bea0141d19c60feb098283" } ,{ "testCaseDescription": "javascript-true-delete-replacement-test", @@ -193,7 +193,7 @@ 1, 1 ], - "name": "true.js", + "filepath": "true.js", "end": [ 1, 13 @@ -210,7 +210,7 @@ 2, 1 ], - "name": "true.js", + "filepath": "true.js", "end": [ 2, 5 @@ -227,7 +227,7 @@ 2, 1 ], - "name": "true.js", + "filepath": "true.js", "end": [ 2, 13 @@ -244,9 +244,9 @@ "filePaths": [ "true.js" ], - "sha1": "20e525bfe23a51c65b7fb2ab38d615b8b79158de", + "sha1": "e9fecdea0ced5209f1bea0141d19c60feb098283", "gitDir": "test/corpus/repos/javascript", - "sha2": "613d3c0edaec792150189c91ad97cc262e325d67" + "sha2": "4c34ae852747f30b9a84a3552152596876080bcb" } ,{ "testCaseDescription": "javascript-true-delete-test", @@ -260,7 +260,7 @@ 1, 1 ], - "name": "true.js", + "filepath": "true.js", "end": [ 1, 5 @@ -277,9 +277,9 @@ "filePaths": [ "true.js" ], - "sha1": "613d3c0edaec792150189c91ad97cc262e325d67", + "sha1": "4c34ae852747f30b9a84a3552152596876080bcb", "gitDir": "test/corpus/repos/javascript", - "sha2": "1d1cf06b41782094ca5aeef9ba6af038f3a58cf8" + "sha2": "f42d40c8860045ca5056d8f459e4f972eb4f23eb" } ,{ "testCaseDescription": "javascript-true-delete-rest-test", @@ -293,7 +293,7 @@ 1, 1 ], - "name": "true.js", + "filepath": "true.js", "end": [ 1, 13 @@ -310,7 +310,7 @@ "filePaths": [ "true.js" ], - "sha1": "1d1cf06b41782094ca5aeef9ba6af038f3a58cf8", + "sha1": "f42d40c8860045ca5056d8f459e4f972eb4f23eb", "gitDir": "test/corpus/repos/javascript", - "sha2": "d72ebc215a9377983c2463fd424f608320626141" + "sha2": "0c49509069b9b1a2dad80bcf2611f5c1b87f07f9" }] diff --git a/test/corpus/diff-summaries/javascript/try-statement.json b/test/corpus/diff-summaries/javascript/try-statement.json index 82f134c76..3d024956a 100644 --- a/test/corpus/diff-summaries/javascript/try-statement.json +++ b/test/corpus/diff-summaries/javascript/try-statement.json @@ -10,7 +10,7 @@ 1, 1 ], - "name": "try-statement.js", + "filepath": "try-statement.js", "end": [ 1, 39 @@ -27,9 +27,9 @@ "filePaths": [ "try-statement.js" ], - "sha1": "37116a9b6cbef2a356805bbeaf6ab65cdcac7749", + "sha1": "60a8828fc9bf6d94594def1279d1bec1e2d57e26", "gitDir": "test/corpus/repos/javascript", - "sha2": "a4e8b07dddedfa2d15a61dbb4b3141e2d9f990e2" + "sha2": "054a281f018e2e09cc4f2d90effaf656688a7768" } ,{ "testCaseDescription": "javascript-try-statement-replacement-insert-test", @@ -43,7 +43,7 @@ 1, 1 ], - "name": "try-statement.js", + "filepath": "try-statement.js", "end": [ 1, 39 @@ -60,7 +60,7 @@ 2, 1 ], - "name": "try-statement.js", + "filepath": "try-statement.js", "end": [ 2, 39 @@ -77,9 +77,9 @@ "filePaths": [ "try-statement.js" ], - "sha1": "a4e8b07dddedfa2d15a61dbb4b3141e2d9f990e2", + "sha1": "054a281f018e2e09cc4f2d90effaf656688a7768", "gitDir": "test/corpus/repos/javascript", - "sha2": "b7d82c2afa8c802c9cc1f12bf9b1482355e78a72" + "sha2": "c495c552becd1ac3f95a5ee8d86e6bb098513b0d" } ,{ "testCaseDescription": "javascript-try-statement-delete-insert-test", @@ -94,7 +94,7 @@ 1, 20 ], - "name": "try-statement.js", + "filepath": "try-statement.js", "end": [ 1, 21 @@ -105,7 +105,7 @@ 1, 20 ], - "name": "try-statement.js", + "filepath": "try-statement.js", "end": [ 1, 21 @@ -124,7 +124,7 @@ 1, 35 ], - "name": "try-statement.js", + "filepath": "try-statement.js", "end": [ 1, 36 @@ -135,7 +135,7 @@ 1, 35 ], - "name": "try-statement.js", + "filepath": "try-statement.js", "end": [ 1, 36 @@ -153,9 +153,9 @@ "filePaths": [ "try-statement.js" ], - "sha1": "b7d82c2afa8c802c9cc1f12bf9b1482355e78a72", + "sha1": "c495c552becd1ac3f95a5ee8d86e6bb098513b0d", "gitDir": "test/corpus/repos/javascript", - "sha2": "d226c84d231a5589a524dfefebf69c7f768bdb07" + "sha2": "51b70762a3831d9681da7d8e5ef7dc1d845b0e69" } ,{ "testCaseDescription": "javascript-try-statement-replacement-test", @@ -170,7 +170,7 @@ 1, 20 ], - "name": "try-statement.js", + "filepath": "try-statement.js", "end": [ 1, 21 @@ -181,7 +181,7 @@ 1, 20 ], - "name": "try-statement.js", + "filepath": "try-statement.js", "end": [ 1, 21 @@ -200,7 +200,7 @@ 1, 35 ], - "name": "try-statement.js", + "filepath": "try-statement.js", "end": [ 1, 36 @@ -211,7 +211,7 @@ 1, 35 ], - "name": "try-statement.js", + "filepath": "try-statement.js", "end": [ 1, 36 @@ -229,9 +229,9 @@ "filePaths": [ "try-statement.js" ], - "sha1": "d226c84d231a5589a524dfefebf69c7f768bdb07", + "sha1": "51b70762a3831d9681da7d8e5ef7dc1d845b0e69", "gitDir": "test/corpus/repos/javascript", - "sha2": "1f2a4307a65b7dfee0c12be6a32d321219823032" + "sha2": "b71fb894809567ac50335c2d2e052dd0e5795749" } ,{ "testCaseDescription": "javascript-try-statement-delete-replacement-test", @@ -245,7 +245,7 @@ 1, 1 ], - "name": "try-statement.js", + "filepath": "try-statement.js", "end": [ 1, 39 @@ -262,7 +262,7 @@ 2, 1 ], - "name": "try-statement.js", + "filepath": "try-statement.js", "end": [ 2, 39 @@ -279,7 +279,7 @@ 2, 1 ], - "name": "try-statement.js", + "filepath": "try-statement.js", "end": [ 2, 39 @@ -296,9 +296,9 @@ "filePaths": [ "try-statement.js" ], - "sha1": "1f2a4307a65b7dfee0c12be6a32d321219823032", + "sha1": "b71fb894809567ac50335c2d2e052dd0e5795749", "gitDir": "test/corpus/repos/javascript", - "sha2": "8c44248e45552ea0890d9af4d83c529c367f0962" + "sha2": "81b001520df1f6fba7bcbe6bf3d40dc2a5e460ee" } ,{ "testCaseDescription": "javascript-try-statement-delete-test", @@ -312,7 +312,7 @@ 1, 1 ], - "name": "try-statement.js", + "filepath": "try-statement.js", "end": [ 1, 39 @@ -329,9 +329,9 @@ "filePaths": [ "try-statement.js" ], - "sha1": "8c44248e45552ea0890d9af4d83c529c367f0962", + "sha1": "81b001520df1f6fba7bcbe6bf3d40dc2a5e460ee", "gitDir": "test/corpus/repos/javascript", - "sha2": "1cfe73a72235d8cddd34b3b206764bb83c2af7bd" + "sha2": "c2bef7133d32ac9f30150f1e83b35ed095ea220d" } ,{ "testCaseDescription": "javascript-try-statement-delete-rest-test", @@ -345,7 +345,7 @@ 1, 1 ], - "name": "try-statement.js", + "filepath": "try-statement.js", "end": [ 1, 39 @@ -362,7 +362,7 @@ "filePaths": [ "try-statement.js" ], - "sha1": "1cfe73a72235d8cddd34b3b206764bb83c2af7bd", + "sha1": "c2bef7133d32ac9f30150f1e83b35ed095ea220d", "gitDir": "test/corpus/repos/javascript", - "sha2": "a2484cda906ab54500ff1a38755f0f7a37c85d77" + "sha2": "a23e0dc447ad61483fbbc0ad63e7d394d7d51dea" }] diff --git a/test/corpus/diff-summaries/javascript/type-operator.json b/test/corpus/diff-summaries/javascript/type-operator.json index dc857dd7b..7fc8a7926 100644 --- a/test/corpus/diff-summaries/javascript/type-operator.json +++ b/test/corpus/diff-summaries/javascript/type-operator.json @@ -10,7 +10,7 @@ 1, 1 ], - "name": "type-operator.js", + "filepath": "type-operator.js", "end": [ 1, 9 @@ -27,9 +27,9 @@ "filePaths": [ "type-operator.js" ], - "sha1": "3da268bcc8f3c57c756ab27cc04835366de458ed", + "sha1": "50309f34c0de7cd11671d67c340e397105e30378", "gitDir": "test/corpus/repos/javascript", - "sha2": "bf52d2757f0b2aea81872b152a265e458e49a704" + "sha2": "75dfb61441800a56abbdd2d5f3c49ce929498774" } ,{ "testCaseDescription": "javascript-type-operator-replacement-insert-test", @@ -43,7 +43,7 @@ 1, 1 ], - "name": "type-operator.js", + "filepath": "type-operator.js", "end": [ 1, 20 @@ -60,7 +60,7 @@ 2, 1 ], - "name": "type-operator.js", + "filepath": "type-operator.js", "end": [ 2, 9 @@ -77,9 +77,9 @@ "filePaths": [ "type-operator.js" ], - "sha1": "bf52d2757f0b2aea81872b152a265e458e49a704", + "sha1": "75dfb61441800a56abbdd2d5f3c49ce929498774", "gitDir": "test/corpus/repos/javascript", - "sha2": "db902da75db1ceb296f0efcd281f20e06881da2a" + "sha2": "d3baaff3ae9c8e6911f3d6ac35cb14aff9110ca7" } ,{ "testCaseDescription": "javascript-type-operator-delete-insert-test", @@ -93,7 +93,7 @@ 1, 14 ], - "name": "type-operator.js", + "filepath": "type-operator.js", "end": [ 1, 20 @@ -110,9 +110,9 @@ "filePaths": [ "type-operator.js" ], - "sha1": "db902da75db1ceb296f0efcd281f20e06881da2a", + "sha1": "d3baaff3ae9c8e6911f3d6ac35cb14aff9110ca7", "gitDir": "test/corpus/repos/javascript", - "sha2": "b1ca63ebe20ccb5ae88740c986028cfe8298f5be" + "sha2": "1a112b34e981bc1cd15628150e13298dcc0a038c" } ,{ "testCaseDescription": "javascript-type-operator-replacement-test", @@ -126,7 +126,7 @@ 1, 14 ], - "name": "type-operator.js", + "filepath": "type-operator.js", "end": [ 1, 20 @@ -143,9 +143,9 @@ "filePaths": [ "type-operator.js" ], - "sha1": "b1ca63ebe20ccb5ae88740c986028cfe8298f5be", + "sha1": "1a112b34e981bc1cd15628150e13298dcc0a038c", "gitDir": "test/corpus/repos/javascript", - "sha2": "aa6bcc1ee4c75cdcfa0f9b2a21d70a746a4b841b" + "sha2": "859ce010a6f087e5a072842b4e61a22100762d0f" } ,{ "testCaseDescription": "javascript-type-operator-delete-replacement-test", @@ -159,7 +159,7 @@ 1, 1 ], - "name": "type-operator.js", + "filepath": "type-operator.js", "end": [ 1, 20 @@ -176,7 +176,7 @@ 2, 1 ], - "name": "type-operator.js", + "filepath": "type-operator.js", "end": [ 2, 9 @@ -193,7 +193,7 @@ 2, 1 ], - "name": "type-operator.js", + "filepath": "type-operator.js", "end": [ 2, 20 @@ -210,9 +210,9 @@ "filePaths": [ "type-operator.js" ], - "sha1": "aa6bcc1ee4c75cdcfa0f9b2a21d70a746a4b841b", + "sha1": "859ce010a6f087e5a072842b4e61a22100762d0f", "gitDir": "test/corpus/repos/javascript", - "sha2": "ae4d8cd401ffeba3bc97c02c1524b37cbfb9faea" + "sha2": "550f116443d9a0e9619700ef7a069d8135464736" } ,{ "testCaseDescription": "javascript-type-operator-delete-test", @@ -226,7 +226,7 @@ 1, 1 ], - "name": "type-operator.js", + "filepath": "type-operator.js", "end": [ 1, 9 @@ -243,9 +243,9 @@ "filePaths": [ "type-operator.js" ], - "sha1": "ae4d8cd401ffeba3bc97c02c1524b37cbfb9faea", + "sha1": "550f116443d9a0e9619700ef7a069d8135464736", "gitDir": "test/corpus/repos/javascript", - "sha2": "3834bbd6381bbddaac82b11cdcd3081dd861055b" + "sha2": "658af676f9be6d61d755518e40f274e7a6fe9480" } ,{ "testCaseDescription": "javascript-type-operator-delete-rest-test", @@ -259,7 +259,7 @@ 1, 1 ], - "name": "type-operator.js", + "filepath": "type-operator.js", "end": [ 1, 20 @@ -276,7 +276,7 @@ "filePaths": [ "type-operator.js" ], - "sha1": "3834bbd6381bbddaac82b11cdcd3081dd861055b", + "sha1": "658af676f9be6d61d755518e40f274e7a6fe9480", "gitDir": "test/corpus/repos/javascript", - "sha2": "1d2c6fd4f13c50341f68aa3be753d5748c072f12" + "sha2": "93c04be8d218fb6138c2fc81022e103318c046be" }] diff --git a/test/corpus/diff-summaries/javascript/undefined.json b/test/corpus/diff-summaries/javascript/undefined.json index bb2cc96c8..3312749bc 100644 --- a/test/corpus/diff-summaries/javascript/undefined.json +++ b/test/corpus/diff-summaries/javascript/undefined.json @@ -10,7 +10,7 @@ 1, 1 ], - "name": "undefined.js", + "filepath": "undefined.js", "end": [ 1, 10 @@ -27,9 +27,9 @@ "filePaths": [ "undefined.js" ], - "sha1": "b12ee7f9618c46965c38b2ba972b8dc99f4db063", + "sha1": "e74587cdf2ae6a791148520a92343b821ff25a39", "gitDir": "test/corpus/repos/javascript", - "sha2": "bb8c48bf8d915b88704830933760b511442cccb9" + "sha2": "a092694dd63b6891fca6a6c01fe6fc311ccfefc0" } ,{ "testCaseDescription": "javascript-undefined-replacement-insert-test", @@ -43,7 +43,7 @@ 1, 1 ], - "name": "undefined.js", + "filepath": "undefined.js", "end": [ 1, 18 @@ -60,7 +60,7 @@ 2, 1 ], - "name": "undefined.js", + "filepath": "undefined.js", "end": [ 2, 10 @@ -77,9 +77,9 @@ "filePaths": [ "undefined.js" ], - "sha1": "bb8c48bf8d915b88704830933760b511442cccb9", + "sha1": "a092694dd63b6891fca6a6c01fe6fc311ccfefc0", "gitDir": "test/corpus/repos/javascript", - "sha2": "300cad620fbf5558e6b7986716bcebe64fd6ebab" + "sha2": "aff210f6517f147413129564c1ae5c80e8c642b5" } ,{ "testCaseDescription": "javascript-undefined-delete-insert-test", @@ -93,7 +93,7 @@ 1, 1 ], - "name": "undefined.js", + "filepath": "undefined.js", "end": [ 1, 10 @@ -110,7 +110,7 @@ 1, 1 ], - "name": "undefined.js", + "filepath": "undefined.js", "end": [ 1, 18 @@ -127,9 +127,9 @@ "filePaths": [ "undefined.js" ], - "sha1": "300cad620fbf5558e6b7986716bcebe64fd6ebab", + "sha1": "aff210f6517f147413129564c1ae5c80e8c642b5", "gitDir": "test/corpus/repos/javascript", - "sha2": "1dce7dbeb8e1cc5831b8129632f92712b61456ee" + "sha2": "df30aaa6b69c0187116e485433f3fa09c111d1c1" } ,{ "testCaseDescription": "javascript-undefined-replacement-test", @@ -143,7 +143,7 @@ 1, 1 ], - "name": "undefined.js", + "filepath": "undefined.js", "end": [ 1, 18 @@ -160,7 +160,7 @@ 1, 1 ], - "name": "undefined.js", + "filepath": "undefined.js", "end": [ 1, 10 @@ -177,9 +177,9 @@ "filePaths": [ "undefined.js" ], - "sha1": "1dce7dbeb8e1cc5831b8129632f92712b61456ee", + "sha1": "df30aaa6b69c0187116e485433f3fa09c111d1c1", "gitDir": "test/corpus/repos/javascript", - "sha2": "ccb167578532dd5e532386c33a1d522b8fd740c8" + "sha2": "bbe0f8cca9475e97c7b596082665021bc776db7f" } ,{ "testCaseDescription": "javascript-undefined-delete-replacement-test", @@ -193,7 +193,7 @@ 1, 1 ], - "name": "undefined.js", + "filepath": "undefined.js", "end": [ 1, 18 @@ -210,7 +210,7 @@ 2, 1 ], - "name": "undefined.js", + "filepath": "undefined.js", "end": [ 2, 10 @@ -227,7 +227,7 @@ 2, 1 ], - "name": "undefined.js", + "filepath": "undefined.js", "end": [ 2, 18 @@ -244,9 +244,9 @@ "filePaths": [ "undefined.js" ], - "sha1": "ccb167578532dd5e532386c33a1d522b8fd740c8", + "sha1": "bbe0f8cca9475e97c7b596082665021bc776db7f", "gitDir": "test/corpus/repos/javascript", - "sha2": "f9717cc0a960d6c1eb489504d00a3db7b7d4b32f" + "sha2": "c21b9ec8fd898eb82469ee50822398a831ce1334" } ,{ "testCaseDescription": "javascript-undefined-delete-test", @@ -260,7 +260,7 @@ 1, 1 ], - "name": "undefined.js", + "filepath": "undefined.js", "end": [ 1, 10 @@ -277,9 +277,9 @@ "filePaths": [ "undefined.js" ], - "sha1": "f9717cc0a960d6c1eb489504d00a3db7b7d4b32f", + "sha1": "c21b9ec8fd898eb82469ee50822398a831ce1334", "gitDir": "test/corpus/repos/javascript", - "sha2": "77a27a5f00ff8905174b049ebdb6e592b86277a4" + "sha2": "dda047c667230759062e03c7ad23b7def28641a0" } ,{ "testCaseDescription": "javascript-undefined-delete-rest-test", @@ -293,7 +293,7 @@ 1, 1 ], - "name": "undefined.js", + "filepath": "undefined.js", "end": [ 1, 18 @@ -310,7 +310,7 @@ "filePaths": [ "undefined.js" ], - "sha1": "77a27a5f00ff8905174b049ebdb6e592b86277a4", + "sha1": "dda047c667230759062e03c7ad23b7def28641a0", "gitDir": "test/corpus/repos/javascript", - "sha2": "33c5c1f9cf953a752cbffb621c3f049a1da56ef6" + "sha2": "d31d85df74e8ffa11d6367b6a2a2fb8505174593" }] diff --git a/test/corpus/diff-summaries/javascript/var-declaration.json b/test/corpus/diff-summaries/javascript/var-declaration.json index 1d5ab9caa..5c1903755 100644 --- a/test/corpus/diff-summaries/javascript/var-declaration.json +++ b/test/corpus/diff-summaries/javascript/var-declaration.json @@ -10,7 +10,7 @@ 1, 5 ], - "name": "var-declaration.js", + "filepath": "var-declaration.js", "end": [ 1, 10 @@ -27,9 +27,9 @@ "filePaths": [ "var-declaration.js" ], - "sha1": "c97ecbdf25494ecedeff774f0dc2dc3e46859eb2", + "sha1": "286453a00dbe069dc12fae9b6fdb767b1cdfa85d", "gitDir": "test/corpus/repos/javascript", - "sha2": "eedc2942855b62115ad5dc3a6627b9f467dc1ded" + "sha2": "9964f50f7b7ff17f32f2231df9d29ad3085c6fcd" } ,{ "testCaseDescription": "javascript-var-declaration-replacement-insert-test", @@ -43,7 +43,7 @@ 1, 5 ], - "name": "var-declaration.js", + "filepath": "var-declaration.js", "end": [ 1, 6 @@ -60,7 +60,7 @@ 1, 8 ], - "name": "var-declaration.js", + "filepath": "var-declaration.js", "end": [ 1, 14 @@ -77,7 +77,7 @@ 1, 16 ], - "name": "var-declaration.js", + "filepath": "var-declaration.js", "end": [ 1, 17 @@ -94,7 +94,7 @@ 2, 5 ], - "name": "var-declaration.js", + "filepath": "var-declaration.js", "end": [ 2, 10 @@ -111,9 +111,9 @@ "filePaths": [ "var-declaration.js" ], - "sha1": "eedc2942855b62115ad5dc3a6627b9f467dc1ded", + "sha1": "9964f50f7b7ff17f32f2231df9d29ad3085c6fcd", "gitDir": "test/corpus/repos/javascript", - "sha2": "1257b186363ddaadbc39499f4bebd1fe1f4e386e" + "sha2": "6c33b4385e09a649d8d4198328e67bc4aa58f2df" } ,{ "testCaseDescription": "javascript-var-declaration-delete-insert-test", @@ -128,7 +128,7 @@ 1, 5 ], - "name": "var-declaration.js", + "filepath": "var-declaration.js", "end": [ 1, 6 @@ -139,7 +139,7 @@ 1, 5 ], - "name": "var-declaration.js", + "filepath": "var-declaration.js", "end": [ 1, 10 @@ -157,7 +157,7 @@ 1, 8 ], - "name": "var-declaration.js", + "filepath": "var-declaration.js", "end": [ 1, 14 @@ -174,7 +174,7 @@ 1, 16 ], - "name": "var-declaration.js", + "filepath": "var-declaration.js", "end": [ 1, 17 @@ -191,9 +191,9 @@ "filePaths": [ "var-declaration.js" ], - "sha1": "1257b186363ddaadbc39499f4bebd1fe1f4e386e", + "sha1": "6c33b4385e09a649d8d4198328e67bc4aa58f2df", "gitDir": "test/corpus/repos/javascript", - "sha2": "4bedf3cf2701ca07d66bb71eb8d2b4ac4f6b4833" + "sha2": "9d343f4bc1a5a06ac722b86c20d7523464a5d1a1" } ,{ "testCaseDescription": "javascript-var-declaration-replacement-test", @@ -208,7 +208,7 @@ 1, 5 ], - "name": "var-declaration.js", + "filepath": "var-declaration.js", "end": [ 1, 10 @@ -219,7 +219,7 @@ 1, 5 ], - "name": "var-declaration.js", + "filepath": "var-declaration.js", "end": [ 1, 6 @@ -237,7 +237,7 @@ 1, 8 ], - "name": "var-declaration.js", + "filepath": "var-declaration.js", "end": [ 1, 14 @@ -254,7 +254,7 @@ 1, 16 ], - "name": "var-declaration.js", + "filepath": "var-declaration.js", "end": [ 1, 17 @@ -271,9 +271,9 @@ "filePaths": [ "var-declaration.js" ], - "sha1": "4bedf3cf2701ca07d66bb71eb8d2b4ac4f6b4833", + "sha1": "9d343f4bc1a5a06ac722b86c20d7523464a5d1a1", "gitDir": "test/corpus/repos/javascript", - "sha2": "bf0dfe0114e3c9edb06bf246a532f5db0109214f" + "sha2": "21b11bcf9b44e07c4f73f1a98be424cb09248151" } ,{ "testCaseDescription": "javascript-var-declaration-delete-replacement-test", @@ -287,7 +287,7 @@ 1, 5 ], - "name": "var-declaration.js", + "filepath": "var-declaration.js", "end": [ 1, 6 @@ -304,7 +304,7 @@ 1, 8 ], - "name": "var-declaration.js", + "filepath": "var-declaration.js", "end": [ 1, 14 @@ -321,7 +321,7 @@ 1, 16 ], - "name": "var-declaration.js", + "filepath": "var-declaration.js", "end": [ 1, 17 @@ -338,7 +338,7 @@ 2, 5 ], - "name": "var-declaration.js", + "filepath": "var-declaration.js", "end": [ 2, 10 @@ -355,7 +355,7 @@ 2, 5 ], - "name": "var-declaration.js", + "filepath": "var-declaration.js", "end": [ 2, 6 @@ -372,7 +372,7 @@ 2, 8 ], - "name": "var-declaration.js", + "filepath": "var-declaration.js", "end": [ 2, 14 @@ -389,7 +389,7 @@ 2, 16 ], - "name": "var-declaration.js", + "filepath": "var-declaration.js", "end": [ 2, 17 @@ -406,9 +406,9 @@ "filePaths": [ "var-declaration.js" ], - "sha1": "bf0dfe0114e3c9edb06bf246a532f5db0109214f", + "sha1": "21b11bcf9b44e07c4f73f1a98be424cb09248151", "gitDir": "test/corpus/repos/javascript", - "sha2": "0b5297915a17bae22d13f9e86d866f6fa878225b" + "sha2": "0958b2b4ff0668da06b8aba0390576578c38e4c5" } ,{ "testCaseDescription": "javascript-var-declaration-delete-test", @@ -422,7 +422,7 @@ 1, 5 ], - "name": "var-declaration.js", + "filepath": "var-declaration.js", "end": [ 1, 10 @@ -439,9 +439,9 @@ "filePaths": [ "var-declaration.js" ], - "sha1": "0b5297915a17bae22d13f9e86d866f6fa878225b", + "sha1": "0958b2b4ff0668da06b8aba0390576578c38e4c5", "gitDir": "test/corpus/repos/javascript", - "sha2": "6890c55ff9c75b2fd4f29a20ac97707e57965ca1" + "sha2": "d28f4dbd6d9c8393afddbba5a65333ed9569fcdc" } ,{ "testCaseDescription": "javascript-var-declaration-delete-rest-test", @@ -455,7 +455,7 @@ 1, 5 ], - "name": "var-declaration.js", + "filepath": "var-declaration.js", "end": [ 1, 6 @@ -472,7 +472,7 @@ 1, 8 ], - "name": "var-declaration.js", + "filepath": "var-declaration.js", "end": [ 1, 14 @@ -489,7 +489,7 @@ 1, 16 ], - "name": "var-declaration.js", + "filepath": "var-declaration.js", "end": [ 1, 17 @@ -506,7 +506,7 @@ "filePaths": [ "var-declaration.js" ], - "sha1": "6890c55ff9c75b2fd4f29a20ac97707e57965ca1", + "sha1": "d28f4dbd6d9c8393afddbba5a65333ed9569fcdc", "gitDir": "test/corpus/repos/javascript", - "sha2": "61540dc73cfaad0786519aca74727ab895384c00" + "sha2": "a10e3508064d97ccd29932d234c261891413b8f1" }] diff --git a/test/corpus/diff-summaries/javascript/variable.json b/test/corpus/diff-summaries/javascript/variable.json index ac8f5964f..72233ac72 100644 --- a/test/corpus/diff-summaries/javascript/variable.json +++ b/test/corpus/diff-summaries/javascript/variable.json @@ -10,7 +10,7 @@ 1, 1 ], - "name": "variable.js", + "filepath": "variable.js", "end": [ 1, 7 @@ -27,9 +27,9 @@ "filePaths": [ "variable.js" ], - "sha1": "76561264ab91701d52dcc8dcbb42c25ea412ae25", + "sha1": "e810690ccde034e2e884c136d22a019fd9d06fc1", "gitDir": "test/corpus/repos/javascript", - "sha2": "677b66a442698673a2e039827f5259f4a618bdf6" + "sha2": "b0f1feffc520e43455292048a0c3f7195f1edd39" } ,{ "testCaseDescription": "javascript-variable-replacement-insert-test", @@ -43,7 +43,7 @@ 1, 1 ], - "name": "variable.js", + "filepath": "variable.js", "end": [ 1, 8 @@ -60,7 +60,7 @@ 2, 1 ], - "name": "variable.js", + "filepath": "variable.js", "end": [ 2, 7 @@ -77,9 +77,9 @@ "filePaths": [ "variable.js" ], - "sha1": "677b66a442698673a2e039827f5259f4a618bdf6", + "sha1": "b0f1feffc520e43455292048a0c3f7195f1edd39", "gitDir": "test/corpus/repos/javascript", - "sha2": "7329fd9a1547c296931f6f4bf9ec680740a94429" + "sha2": "00bfd61614ed3ad793d8dd2edbf61a6c0b0e8c47" } ,{ "testCaseDescription": "javascript-variable-delete-insert-test", @@ -94,7 +94,7 @@ 1, 1 ], - "name": "variable.js", + "filepath": "variable.js", "end": [ 1, 8 @@ -105,7 +105,7 @@ 1, 1 ], - "name": "variable.js", + "filepath": "variable.js", "end": [ 1, 7 @@ -123,9 +123,9 @@ "filePaths": [ "variable.js" ], - "sha1": "7329fd9a1547c296931f6f4bf9ec680740a94429", + "sha1": "00bfd61614ed3ad793d8dd2edbf61a6c0b0e8c47", "gitDir": "test/corpus/repos/javascript", - "sha2": "8a8aa0a0874f8e702f3699af10a85abda3647742" + "sha2": "d35ffaac041e794f92aef34d39e3c93b0a8df1f1" } ,{ "testCaseDescription": "javascript-variable-replacement-test", @@ -140,7 +140,7 @@ 1, 1 ], - "name": "variable.js", + "filepath": "variable.js", "end": [ 1, 7 @@ -151,7 +151,7 @@ 1, 1 ], - "name": "variable.js", + "filepath": "variable.js", "end": [ 1, 8 @@ -169,9 +169,9 @@ "filePaths": [ "variable.js" ], - "sha1": "8a8aa0a0874f8e702f3699af10a85abda3647742", + "sha1": "d35ffaac041e794f92aef34d39e3c93b0a8df1f1", "gitDir": "test/corpus/repos/javascript", - "sha2": "21de27cee9675fb27ed7fe0b27cc12ac59bb70fd" + "sha2": "b182b97677c7e8934ee9cc8110c08b269d9abb63" } ,{ "testCaseDescription": "javascript-variable-delete-replacement-test", @@ -185,7 +185,7 @@ 1, 1 ], - "name": "variable.js", + "filepath": "variable.js", "end": [ 1, 8 @@ -202,7 +202,7 @@ 2, 1 ], - "name": "variable.js", + "filepath": "variable.js", "end": [ 2, 7 @@ -219,7 +219,7 @@ 2, 1 ], - "name": "variable.js", + "filepath": "variable.js", "end": [ 2, 8 @@ -236,9 +236,9 @@ "filePaths": [ "variable.js" ], - "sha1": "21de27cee9675fb27ed7fe0b27cc12ac59bb70fd", + "sha1": "b182b97677c7e8934ee9cc8110c08b269d9abb63", "gitDir": "test/corpus/repos/javascript", - "sha2": "ac2b7f461f6de872b99447ea68b864915618c938" + "sha2": "4b996eed16cfeb3010f850ab320e380609204140" } ,{ "testCaseDescription": "javascript-variable-delete-test", @@ -252,7 +252,7 @@ 1, 1 ], - "name": "variable.js", + "filepath": "variable.js", "end": [ 1, 7 @@ -269,9 +269,9 @@ "filePaths": [ "variable.js" ], - "sha1": "ac2b7f461f6de872b99447ea68b864915618c938", + "sha1": "4b996eed16cfeb3010f850ab320e380609204140", "gitDir": "test/corpus/repos/javascript", - "sha2": "e517079aa213f18fcf8c0152222655a6ac3738cb" + "sha2": "84c62bb7eb095d59e0b684d4681bc8255984f835" } ,{ "testCaseDescription": "javascript-variable-delete-rest-test", @@ -285,7 +285,7 @@ 1, 1 ], - "name": "variable.js", + "filepath": "variable.js", "end": [ 1, 8 @@ -302,7 +302,7 @@ "filePaths": [ "variable.js" ], - "sha1": "e517079aa213f18fcf8c0152222655a6ac3738cb", + "sha1": "84c62bb7eb095d59e0b684d4681bc8255984f835", "gitDir": "test/corpus/repos/javascript", - "sha2": "ea0156c09a6d9c183d037bddda50ce815c00548f" + "sha2": "61c4e25d974e0e9cf017918a46a3cd735b8459be" }] diff --git a/test/corpus/diff-summaries/javascript/void-operator.json b/test/corpus/diff-summaries/javascript/void-operator.json index e2ec17ccc..2f57f3b70 100644 --- a/test/corpus/diff-summaries/javascript/void-operator.json +++ b/test/corpus/diff-summaries/javascript/void-operator.json @@ -10,7 +10,7 @@ 1, 1 ], - "name": "void-operator.js", + "filepath": "void-operator.js", "end": [ 1, 9 @@ -27,9 +27,9 @@ "filePaths": [ "void-operator.js" ], - "sha1": "f8fceed82b3d3f5189fd21d8dd7a5589c803ba0e", + "sha1": "2fe5894d4f539f52e189f03e679cc3e8b733fa22", "gitDir": "test/corpus/repos/javascript", - "sha2": "7998c6269fdd9a217d72c31e2a1f03fc53b0e8b5" + "sha2": "4353af1d1a1c0c72044fb3a5c726db2fac5f5f2d" } ,{ "testCaseDescription": "javascript-void-operator-replacement-insert-test", @@ -43,7 +43,7 @@ 1, 1 ], - "name": "void-operator.js", + "filepath": "void-operator.js", "end": [ 1, 9 @@ -60,7 +60,7 @@ 2, 1 ], - "name": "void-operator.js", + "filepath": "void-operator.js", "end": [ 2, 9 @@ -77,9 +77,9 @@ "filePaths": [ "void-operator.js" ], - "sha1": "7998c6269fdd9a217d72c31e2a1f03fc53b0e8b5", + "sha1": "4353af1d1a1c0c72044fb3a5c726db2fac5f5f2d", "gitDir": "test/corpus/repos/javascript", - "sha2": "1d89bdb5c21c95655bc123cde876265833d8ffc9" + "sha2": "85048410444e9b90642363abef7ed19624fffb64" } ,{ "testCaseDescription": "javascript-void-operator-delete-insert-test", @@ -94,7 +94,7 @@ 1, 6 ], - "name": "void-operator.js", + "filepath": "void-operator.js", "end": [ 1, 7 @@ -105,7 +105,7 @@ 1, 6 ], - "name": "void-operator.js", + "filepath": "void-operator.js", "end": [ 1, 7 @@ -123,9 +123,9 @@ "filePaths": [ "void-operator.js" ], - "sha1": "1d89bdb5c21c95655bc123cde876265833d8ffc9", + "sha1": "85048410444e9b90642363abef7ed19624fffb64", "gitDir": "test/corpus/repos/javascript", - "sha2": "85960c0618449d02f5bd903400b67aaf2e2f3339" + "sha2": "a7a10af058c7fa422a29f23c3e06bd1d518400d8" } ,{ "testCaseDescription": "javascript-void-operator-replacement-test", @@ -140,7 +140,7 @@ 1, 6 ], - "name": "void-operator.js", + "filepath": "void-operator.js", "end": [ 1, 7 @@ -151,7 +151,7 @@ 1, 6 ], - "name": "void-operator.js", + "filepath": "void-operator.js", "end": [ 1, 7 @@ -169,9 +169,9 @@ "filePaths": [ "void-operator.js" ], - "sha1": "85960c0618449d02f5bd903400b67aaf2e2f3339", + "sha1": "a7a10af058c7fa422a29f23c3e06bd1d518400d8", "gitDir": "test/corpus/repos/javascript", - "sha2": "9bbed4dcc43d4ecb67ce417bc49cd547eb5f0b84" + "sha2": "bd43bdbe7971b5a68c05949d826fcffd4edca051" } ,{ "testCaseDescription": "javascript-void-operator-delete-replacement-test", @@ -185,7 +185,7 @@ 1, 1 ], - "name": "void-operator.js", + "filepath": "void-operator.js", "end": [ 1, 9 @@ -202,7 +202,7 @@ 2, 1 ], - "name": "void-operator.js", + "filepath": "void-operator.js", "end": [ 2, 9 @@ -219,7 +219,7 @@ 2, 1 ], - "name": "void-operator.js", + "filepath": "void-operator.js", "end": [ 2, 9 @@ -236,9 +236,9 @@ "filePaths": [ "void-operator.js" ], - "sha1": "9bbed4dcc43d4ecb67ce417bc49cd547eb5f0b84", + "sha1": "bd43bdbe7971b5a68c05949d826fcffd4edca051", "gitDir": "test/corpus/repos/javascript", - "sha2": "7ba4114b3c382854daad0d29360ec603919f3a8e" + "sha2": "201c3058d89e1e6e83974f3fc3bd75348b4582aa" } ,{ "testCaseDescription": "javascript-void-operator-delete-test", @@ -252,7 +252,7 @@ 1, 1 ], - "name": "void-operator.js", + "filepath": "void-operator.js", "end": [ 1, 9 @@ -269,9 +269,9 @@ "filePaths": [ "void-operator.js" ], - "sha1": "7ba4114b3c382854daad0d29360ec603919f3a8e", + "sha1": "201c3058d89e1e6e83974f3fc3bd75348b4582aa", "gitDir": "test/corpus/repos/javascript", - "sha2": "ec90e67790d2c3b9340ca93cf2d18fb2a51392f1" + "sha2": "08b8731ba61b1ae6a7283db2331e014b01b1a2c4" } ,{ "testCaseDescription": "javascript-void-operator-delete-rest-test", @@ -285,7 +285,7 @@ 1, 1 ], - "name": "void-operator.js", + "filepath": "void-operator.js", "end": [ 1, 9 @@ -302,7 +302,7 @@ "filePaths": [ "void-operator.js" ], - "sha1": "ec90e67790d2c3b9340ca93cf2d18fb2a51392f1", + "sha1": "08b8731ba61b1ae6a7283db2331e014b01b1a2c4", "gitDir": "test/corpus/repos/javascript", - "sha2": "5fc82ac3374f4c8d50af76e2ae299a59e4cff396" + "sha2": "3f0c7d0c9c68491b7ab4f2a191cc755d276a60ce" }] diff --git a/test/corpus/diff-summaries/javascript/while-statement.json b/test/corpus/diff-summaries/javascript/while-statement.json index c9cad42d9..03145485b 100644 --- a/test/corpus/diff-summaries/javascript/while-statement.json +++ b/test/corpus/diff-summaries/javascript/while-statement.json @@ -10,7 +10,7 @@ 1, 1 ], - "name": "while-statement.js", + "filepath": "while-statement.js", "end": [ 1, 19 @@ -27,9 +27,9 @@ "filePaths": [ "while-statement.js" ], - "sha1": "536e58f01a1c35bfed654e16dc15d4b2636913b7", + "sha1": "8f8662bfef010ed6610d7ee5f21efbbcb97f0d22", "gitDir": "test/corpus/repos/javascript", - "sha2": "9fd0ed71c7fabfc6749ea3c9c9bee28325abff3d" + "sha2": "3ebecc4c6b3f161b3afb23a002547a8da923e2ac" } ,{ "testCaseDescription": "javascript-while-statement-replacement-insert-test", @@ -43,7 +43,7 @@ 1, 1 ], - "name": "while-statement.js", + "filepath": "while-statement.js", "end": [ 1, 19 @@ -60,7 +60,7 @@ 2, 1 ], - "name": "while-statement.js", + "filepath": "while-statement.js", "end": [ 2, 19 @@ -77,9 +77,9 @@ "filePaths": [ "while-statement.js" ], - "sha1": "9fd0ed71c7fabfc6749ea3c9c9bee28325abff3d", + "sha1": "3ebecc4c6b3f161b3afb23a002547a8da923e2ac", "gitDir": "test/corpus/repos/javascript", - "sha2": "b78d260ef2d0c3127aad32afc1cce7f94538c8b7" + "sha2": "b710fc3829752e0e2f783529cfc728317366ce1d" } ,{ "testCaseDescription": "javascript-while-statement-delete-insert-test", @@ -94,7 +94,7 @@ 1, 8 ], - "name": "while-statement.js", + "filepath": "while-statement.js", "end": [ 1, 9 @@ -105,7 +105,7 @@ 1, 8 ], - "name": "while-statement.js", + "filepath": "while-statement.js", "end": [ 1, 9 @@ -124,7 +124,7 @@ 1, 13 ], - "name": "while-statement.js", + "filepath": "while-statement.js", "end": [ 1, 14 @@ -135,7 +135,7 @@ 1, 13 ], - "name": "while-statement.js", + "filepath": "while-statement.js", "end": [ 1, 14 @@ -153,9 +153,9 @@ "filePaths": [ "while-statement.js" ], - "sha1": "b78d260ef2d0c3127aad32afc1cce7f94538c8b7", + "sha1": "b710fc3829752e0e2f783529cfc728317366ce1d", "gitDir": "test/corpus/repos/javascript", - "sha2": "399b7cbb6a6483291a0d018f1e2281a45361c7b1" + "sha2": "4fdfc8d1995201b17731696441cfb578593d79be" } ,{ "testCaseDescription": "javascript-while-statement-replacement-test", @@ -170,7 +170,7 @@ 1, 8 ], - "name": "while-statement.js", + "filepath": "while-statement.js", "end": [ 1, 9 @@ -181,7 +181,7 @@ 1, 8 ], - "name": "while-statement.js", + "filepath": "while-statement.js", "end": [ 1, 9 @@ -200,7 +200,7 @@ 1, 13 ], - "name": "while-statement.js", + "filepath": "while-statement.js", "end": [ 1, 14 @@ -211,7 +211,7 @@ 1, 13 ], - "name": "while-statement.js", + "filepath": "while-statement.js", "end": [ 1, 14 @@ -229,9 +229,9 @@ "filePaths": [ "while-statement.js" ], - "sha1": "399b7cbb6a6483291a0d018f1e2281a45361c7b1", + "sha1": "4fdfc8d1995201b17731696441cfb578593d79be", "gitDir": "test/corpus/repos/javascript", - "sha2": "a01f0234b0944a97f30e87e74475f16104ba25e6" + "sha2": "d502c2b2c439bdd4887a57a2f08d5a1adeaf7aeb" } ,{ "testCaseDescription": "javascript-while-statement-delete-replacement-test", @@ -245,7 +245,7 @@ 1, 1 ], - "name": "while-statement.js", + "filepath": "while-statement.js", "end": [ 1, 19 @@ -262,7 +262,7 @@ 2, 1 ], - "name": "while-statement.js", + "filepath": "while-statement.js", "end": [ 2, 19 @@ -279,7 +279,7 @@ 2, 1 ], - "name": "while-statement.js", + "filepath": "while-statement.js", "end": [ 2, 19 @@ -296,9 +296,9 @@ "filePaths": [ "while-statement.js" ], - "sha1": "a01f0234b0944a97f30e87e74475f16104ba25e6", + "sha1": "d502c2b2c439bdd4887a57a2f08d5a1adeaf7aeb", "gitDir": "test/corpus/repos/javascript", - "sha2": "775cc5eeed82a76131e5dff1a794fc408ad42f32" + "sha2": "1f4ec236c271656f96e2114616adbcf96ec49fd2" } ,{ "testCaseDescription": "javascript-while-statement-delete-test", @@ -312,7 +312,7 @@ 1, 1 ], - "name": "while-statement.js", + "filepath": "while-statement.js", "end": [ 1, 19 @@ -329,9 +329,9 @@ "filePaths": [ "while-statement.js" ], - "sha1": "775cc5eeed82a76131e5dff1a794fc408ad42f32", + "sha1": "1f4ec236c271656f96e2114616adbcf96ec49fd2", "gitDir": "test/corpus/repos/javascript", - "sha2": "7fac6925a6d8770e05a062fcf60f512e2fc6a866" + "sha2": "f75c1b168d8a6440244dcbc2c9551c53095215d6" } ,{ "testCaseDescription": "javascript-while-statement-delete-rest-test", @@ -345,7 +345,7 @@ 1, 1 ], - "name": "while-statement.js", + "filepath": "while-statement.js", "end": [ 1, 19 @@ -362,7 +362,7 @@ "filePaths": [ "while-statement.js" ], - "sha1": "7fac6925a6d8770e05a062fcf60f512e2fc6a866", + "sha1": "f75c1b168d8a6440244dcbc2c9551c53095215d6", "gitDir": "test/corpus/repos/javascript", - "sha2": "ea67bdfe9d16bfb0ba0858898f969294740b84fb" + "sha2": "0b9cb36a4b22cb0b53f5399d40f90e2732f834a6" }] diff --git a/test/corpus/repos/javascript b/test/corpus/repos/javascript index 215d10e67..9455d4cb1 160000 --- a/test/corpus/repos/javascript +++ b/test/corpus/repos/javascript @@ -1 +1 @@ -Subproject commit 215d10e67e03c8e29f188758043ace6b619b01e5 +Subproject commit 9455d4cb158d3f5131c688e7909b842436c06205 From c0ae593a06a441977307433c7a8ef63e1c7d10e1 Mon Sep 17 00:00:00 2001 From: joshvera Date: Tue, 11 Oct 2016 13:08:12 -0400 Subject: [PATCH 23/27] Remove filepath from SourceSpan --- src/SourceSpan.hs | 16 +++------------- 1 file changed, 3 insertions(+), 13 deletions(-) diff --git a/src/SourceSpan.hs b/src/SourceSpan.hs index 040de09c0..e043d0a19 100644 --- a/src/SourceSpan.hs +++ b/src/SourceSpan.hs @@ -41,13 +41,9 @@ instance A.FromJSON SourcePos where data SourceSpan = SourceSpan { -- | - -- Source name - -- - spanName :: !Text - -- | -- Start of the span -- - , spanStart :: !SourcePos + spanStart :: !SourcePos -- End of the span -- , spanEnd :: !SourcePos @@ -57,21 +53,15 @@ displayStartEndPos :: SourceSpan -> Text displayStartEndPos sp = displaySourcePos (spanStart sp) <> " - " <> displaySourcePos (spanEnd sp) -displaySourceSpan :: SourceSpan -> Text -displaySourceSpan sp = - spanName sp <> " " <> displayStartEndPos sp - instance A.ToJSON SourceSpan where toJSON SourceSpan{..} = - A.object [ "filepath" .= spanName - , "start" .= spanStart + A.object [ "start" .= spanStart , "end" .= spanEnd ] instance A.FromJSON SourceSpan where parseJSON = A.withObject "SourceSpan" $ \o -> SourceSpan <$> - o .: "filepath" <*> o .: "start" <*> o .: "end" @@ -94,5 +84,5 @@ instance Arbitrary SourcePos where shrink = genericShrink instance Arbitrary SourceSpan where - arbitrary = SourceSpan <$> arbitrary <*> arbitrary <*> arbitrary + arbitrary = SourceSpan <$> arbitrary <*> arbitrary shrink = genericShrink From 098655b1d9ab584ab7992cff6a9f1018d879ab9e Mon Sep 17 00:00:00 2001 From: joshvera Date: Tue, 11 Oct 2016 15:09:24 -0400 Subject: [PATCH 24/27] Remove filepath from SourceSpan --- src/DiffSummary.hs | 2 +- src/Diffing.hs | 4 ++-- src/Language/Markdown.hs | 4 ++-- src/Source.hs | 4 ++-- src/TreeSitter.hs | 6 +----- 5 files changed, 8 insertions(+), 12 deletions(-) diff --git a/src/DiffSummary.hs b/src/DiffSummary.hs index 8f76b0052..dc120d1ef 100644 --- a/src/DiffSummary.hs +++ b/src/DiffSummary.hs @@ -341,4 +341,4 @@ instance Arbitrary a => Arbitrary (DiffSummary a) where instance P.Pretty DiffInfo where pretty LeafInfo{..} = squotes (string $ toSL termName) <+> string (toSL categoryName) pretty BranchInfo{..} = mconcat $ punctuate (string "," P.<> space) (pretty <$> branches) - pretty ErrorInfo{..} = squotes (string $ toSL termName) <+> "at" <+> (string . toSL $ displayStartEndPos errorSpan) <+> "in" <+> (string . toSL $ spanName errorSpan) + pretty ErrorInfo{..} = squotes (string $ toSL termName) <+> "at" <+> (string . toSL $ displayStartEndPos errorSpan) diff --git a/src/Diffing.hs b/src/Diffing.hs index dc338b29d..2bea415b9 100644 --- a/src/Diffing.hs +++ b/src/Diffing.hs @@ -82,8 +82,8 @@ lineByLineParser SourceBlob{..} = pure . cofree . root $ case foldl' annotateLea (leaves, _) -> cofree <$> leaves where lines = actualLines source - root children = (Range 0 (length source) .: Program .: rangeToSourceSpan source (toS path) (Range 0 (length source)) .: RNil) :< Indexed children - leaf charIndex line = (Range charIndex (charIndex + T.length line) .: Program .: rangeToSourceSpan source (toS path) (Range charIndex (charIndex + T.length line)) .: RNil) :< Leaf line + root children = (Range 0 (length source) .: Program .: rangeToSourceSpan source (Range 0 (length source)) .: RNil) :< Indexed children + leaf charIndex line = (Range charIndex (charIndex + T.length line) .: Program .: rangeToSourceSpan source (Range charIndex (charIndex + T.length line)) .: RNil) :< Leaf line annotateLeaves (accum, charIndex) line = (accum <> [ leaf charIndex (toText line) ] , charIndex + length line) toText = T.pack . Source.toString diff --git a/src/Language/Markdown.hs b/src/Language/Markdown.hs index 3430ed9a1..62ed99fcb 100644 --- a/src/Language/Markdown.hs +++ b/src/Language/Markdown.hs @@ -12,7 +12,7 @@ import Source import Syntax cmarkParser :: Parser (Syntax Text) (Record '[Range, Category, SourceSpan]) -cmarkParser SourceBlob{..} = pure . toTerm (totalRange source) (rangeToSourceSpan source (toS path) $ totalRange source) $ commonmarkToNode [ optSourcePos, optSafe ] (toText source) +cmarkParser SourceBlob{..} = pure . toTerm (totalRange source) (rangeToSourceSpan source $ totalRange source) $ commonmarkToNode [ optSourcePos, optSafe ] (toText source) where toTerm :: Range -> SourceSpan -> Node -> Cofree (Syntax Text) (Record '[Range, Category, SourceSpan]) toTerm within withinSpan (Node position t children) = let @@ -39,4 +39,4 @@ cmarkParser SourceBlob{..} = pure . toTerm (totalRange source) (rangeToSourceSpa toCategory LINK{} = Other "link" toCategory IMAGE{} = Other "image" toCategory t = Other (show t) - toSpan PosInfo{..} = SourceSpan "" (SourcePos (pred startLine) (pred startColumn)) (SourcePos (pred endLine) endColumn) + toSpan PosInfo{..} = SourceSpan (SourcePos (pred startLine) (pred startColumn)) (SourcePos (pred endLine) endColumn) diff --git a/src/Source.hs b/src/Source.hs index 4e5b9a024..a66d6c8fe 100644 --- a/src/Source.hs +++ b/src/Source.hs @@ -99,8 +99,8 @@ sourceSpanToRange source SourceSpan{..} = Range start end (leadingRanges, remainingRanges) = splitAt (line spanStart) (actualLineRanges (totalRange source) source) sumLengths = sum . fmap (\ Range{..} -> end - start) -rangeToSourceSpan :: Source Char -> Text -> Range -> SourceSpan -rangeToSourceSpan source name range@Range{} = SourceSpan name startPos endPos +rangeToSourceSpan :: Source Char -> Range -> SourceSpan +rangeToSourceSpan source range@Range{} = SourceSpan startPos endPos where startPos = maybe (SourcePos 1 1) (toStartPos 1) (head lineRanges) endPos = toEndPos (length lineRanges) (last lineRanges) lineRanges = actualLineRanges range source diff --git a/src/TreeSitter.hs b/src/TreeSitter.hs index 54dfdf003..d749f38ea 100644 --- a/src/TreeSitter.hs +++ b/src/TreeSitter.hs @@ -45,11 +45,7 @@ documentToTerm language document SourceBlob{..} = alloca $ \ root -> do let startPos = SourcePos (1 + (fromIntegral $! ts_node_p_start_point_row node)) (1 + (fromIntegral $! ts_node_p_start_point_column node)) let endPos = SourcePos (1 + (fromIntegral $! ts_node_p_end_point_row node)) (1 + (fromIntegral $! ts_node_p_end_point_column node)) - let sourceSpan = SourceSpan { - spanName = toS path - , spanStart = startPos - , spanEnd = endPos - } + let sourceSpan = SourceSpan { spanStart = startPos , spanEnd = endPos } -- Note: The strict application here is semantically important. -- Without it, we may not evaluate the range until after we’ve exited From deb5a0f018898c3f7a8bda5b4e905c046198c885 Mon Sep 17 00:00:00 2001 From: joshvera Date: Tue, 11 Oct 2016 15:12:48 -0400 Subject: [PATCH 25/27] Fix SourceSpan in tests --- test/DiffSummarySpec.hs | 2 +- test/Source/Spec.hs | 8 ++++---- 2 files changed, 5 insertions(+), 5 deletions(-) diff --git a/test/DiffSummarySpec.hs b/test/DiffSummarySpec.hs index 9eeaec446..fa0670ee0 100644 --- a/test/DiffSummarySpec.hs +++ b/test/DiffSummarySpec.hs @@ -23,7 +23,7 @@ import Test.Hspec.QuickCheck import Data.These sourceSpanBetween :: (Int, Int) -> (Int, Int) -> SourceSpan -sourceSpanBetween (s1, e1) (s2, e2) = SourceSpan "" (SourcePos s1 e1) (SourcePos s2 e2) +sourceSpanBetween (s1, e1) (s2, e2) = SourceSpan (SourcePos s1 e1) (SourcePos s2 e2) arrayInfo :: Record '[Category, Range, SourceSpan] arrayInfo = ArrayLiteral .: Range 0 3 .: sourceSpanBetween (1, 1) (1, 5) .: RNil diff --git a/test/Source/Spec.hs b/test/Source/Spec.hs index 810578eb9..e767a3ebc 100644 --- a/test/Source/Spec.hs +++ b/test/Source/Spec.hs @@ -21,7 +21,7 @@ spec = parallel $ do describe "sourceSpanToRange" $ do prop "computes single-line ranges" $ \ s -> let source = fromList s - spans = zipWith (\ i Range {..} -> SourceSpan "" (SourcePos i 0) (SourcePos i (end - start))) [0..] ranges + spans = zipWith (\ i Range {..} -> SourceSpan (SourcePos i 0) (SourcePos i (end - start))) [0..] ranges ranges = actualLineRanges (totalRange source) source in sourceSpanToRange source <$> spans `shouldBe` ranges @@ -35,13 +35,13 @@ spec = parallel $ do describe "totalSpan" $ do prop "covers single lines" $ - \ n -> totalSpan (fromList (replicate n '*')) `shouldBe` SourceSpan "" (SourcePos 0 0) (SourcePos 0 (max 0 n)) + \ n -> totalSpan (fromList (replicate n '*')) `shouldBe` SourceSpan (SourcePos 0 0) (SourcePos 0 (max 0 n)) prop "covers multiple lines" $ - \ n -> totalSpan (fromList (intersperse '\n' (replicate n '*'))) `shouldBe` SourceSpan "" (SourcePos 0 0) (SourcePos (max 0 (pred n)) (if n > 0 then 1 else 0)) + \ n -> totalSpan (fromList (intersperse '\n' (replicate n '*'))) `shouldBe` SourceSpan (SourcePos 0 0) (SourcePos (max 0 (pred n)) (if n > 0 then 1 else 0)) totalSpan :: Source Char -> SourceSpan -totalSpan source = SourceSpan "" (SourcePos 0 0) (SourcePos (pred (length ranges)) (end lastRange - start lastRange)) +totalSpan source = SourceSpan (SourcePos 0 0) (SourcePos (pred (length ranges)) (end lastRange - start lastRange)) where ranges = actualLineRanges (totalRange source) source lastRange = Prelude.last ranges From 440d1682739feb2639aea56ced2be725f22ffdac Mon Sep 17 00:00:00 2001 From: joshvera Date: Tue, 11 Oct 2016 15:13:51 -0400 Subject: [PATCH 26/27] bump tests --- .../javascript/anonymous-function.json | 52 ++--- .../anonymous-parameterless-function.json | 40 ++-- .../diff-summaries/javascript/array.json | 38 ++-- .../javascript/arrow-function.json | 40 ++-- .../diff-summaries/javascript/assignment.json | 40 ++-- .../javascript/bitwise-operator.json | 40 ++-- .../javascript/boolean-operator.json | 34 ++- .../javascript/chained-callbacks.json | 48 ++--- .../javascript/chained-property-access.json | 44 ++-- .../diff-summaries/javascript/class.json | 48 ++--- .../javascript/comma-operator.json | 46 ++--- .../diff-summaries/javascript/comment.json | 40 ++-- .../javascript/constructor-call.json | 40 ++-- .../javascript/delete-operator.json | 40 ++-- .../javascript/do-while-statement.json | 44 ++-- .../diff-summaries/javascript/false.json | 40 ++-- .../javascript/for-in-statement.json | 48 ++--- .../for-loop-with-in-statement.json | 44 ++-- .../javascript/for-of-statement.json | 48 ++--- .../javascript/for-statement.json | 40 ++-- .../javascript/function-call-args.json | 60 ++---- .../javascript/function-call.json | 40 ++-- .../diff-summaries/javascript/function.json | 40 ++-- .../javascript/generator-function.json | 40 ++-- .../diff-summaries/javascript/identifier.json | 40 ++-- .../diff-summaries/javascript/if-else.json | 40 ++-- test/corpus/diff-summaries/javascript/if.json | 40 ++-- .../diff-summaries/javascript/import.json | 168 ++------------- .../javascript/math-assignment-operator.json | 40 ++-- .../javascript/math-operator.json | 44 ++-- .../javascript/member-access-assignment.json | 40 ++-- .../javascript/member-access.json | 40 ++-- .../javascript/method-call.json | 40 ++-- .../javascript/named-function.json | 48 ++--- .../nested-do-while-in-function.json | 194 ++---------------- .../javascript/nested-functions.json | 44 ++-- .../diff-summaries/javascript/null.json | 40 ++-- .../diff-summaries/javascript/number.json | 40 ++-- .../javascript/object-with-methods.json | 40 ++-- .../diff-summaries/javascript/object.json | 40 ++-- .../diff-summaries/javascript/regex.json | 40 ++-- .../javascript/relational-operator.json | 34 ++- .../javascript/return-statement.json | 38 ++-- .../diff-summaries/javascript/string.json | 40 ++-- .../subscript-access-assignment.json | 40 ++-- .../javascript/subscript-access-string.json | 40 ++-- .../javascript/subscript-access-variable.json | 40 ++-- .../javascript/switch-statement.json | 44 ++-- .../javascript/template-string.json | 40 ++-- .../diff-summaries/javascript/ternary.json | 40 ++-- .../javascript/this-expression.json | 40 ++-- .../javascript/throw-statement.json | 40 ++-- .../diff-summaries/javascript/true.json | 40 ++-- .../javascript/try-statement.json | 44 ++-- .../javascript/type-operator.json | 38 ++-- .../diff-summaries/javascript/undefined.json | 40 ++-- .../javascript/var-declaration.json | 52 ++--- .../diff-summaries/javascript/variable.json | 40 ++-- .../javascript/void-operator.json | 40 ++-- .../javascript/while-statement.json | 44 ++-- test/corpus/repos/javascript | 2 +- 61 files changed, 841 insertions(+), 1947 deletions(-) diff --git a/test/corpus/diff-summaries/javascript/anonymous-function.json b/test/corpus/diff-summaries/javascript/anonymous-function.json index b1bdd5228..ad31e86fb 100644 --- a/test/corpus/diff-summaries/javascript/anonymous-function.json +++ b/test/corpus/diff-summaries/javascript/anonymous-function.json @@ -10,7 +10,6 @@ 1, 1 ], - "filepath": "anonymous-function.js", "end": [ 1, 32 @@ -27,9 +26,9 @@ "filePaths": [ "anonymous-function.js" ], - "sha1": "b33f47fbe6d253fd1ee502cda8ef5cd4bd771b42", + "sha1": "9a3c8e5bfb1ca123cfbbeefbe9069ecc0bb85fa4", "gitDir": "test/corpus/repos/javascript", - "sha2": "864f71e7429b9e61840bded79c38a88a497f0a30" + "sha2": "499d32d46d3eb5785dbb27e3b56a0894823ee9dd" } ,{ "testCaseDescription": "javascript-anonymous-function-replacement-insert-test", @@ -43,7 +42,6 @@ 1, 1 ], - "filepath": "anonymous-function.js", "end": [ 1, 32 @@ -60,7 +58,6 @@ 2, 1 ], - "filepath": "anonymous-function.js", "end": [ 2, 32 @@ -77,9 +74,9 @@ "filePaths": [ "anonymous-function.js" ], - "sha1": "864f71e7429b9e61840bded79c38a88a497f0a30", + "sha1": "499d32d46d3eb5785dbb27e3b56a0894823ee9dd", "gitDir": "test/corpus/repos/javascript", - "sha2": "d03a926d4d05c1a255a7a0cfc9b56d47d78ae9bb" + "sha2": "20922f45f08fe649a067e60016ed60a67c2c1c7e" } ,{ "testCaseDescription": "javascript-anonymous-function-delete-insert-test", @@ -94,7 +91,6 @@ 1, 10 ], - "filepath": "anonymous-function.js", "end": [ 1, 11 @@ -105,7 +101,6 @@ 1, 10 ], - "filepath": "anonymous-function.js", "end": [ 1, 11 @@ -124,7 +119,6 @@ 1, 12 ], - "filepath": "anonymous-function.js", "end": [ 1, 13 @@ -135,7 +129,6 @@ 1, 12 ], - "filepath": "anonymous-function.js", "end": [ 1, 13 @@ -154,7 +147,6 @@ 1, 24 ], - "filepath": "anonymous-function.js", "end": [ 1, 25 @@ -165,7 +157,6 @@ 1, 24 ], - "filepath": "anonymous-function.js", "end": [ 1, 25 @@ -184,7 +175,6 @@ 1, 28 ], - "filepath": "anonymous-function.js", "end": [ 1, 29 @@ -195,7 +185,6 @@ 1, 28 ], - "filepath": "anonymous-function.js", "end": [ 1, 29 @@ -213,9 +202,9 @@ "filePaths": [ "anonymous-function.js" ], - "sha1": "d03a926d4d05c1a255a7a0cfc9b56d47d78ae9bb", + "sha1": "20922f45f08fe649a067e60016ed60a67c2c1c7e", "gitDir": "test/corpus/repos/javascript", - "sha2": "17f190c1e1d695127ad44863ac2d576475829a7a" + "sha2": "6fc93b6614e4cfff72463ca12e9987c14fb24c6f" } ,{ "testCaseDescription": "javascript-anonymous-function-replacement-test", @@ -230,7 +219,6 @@ 1, 10 ], - "filepath": "anonymous-function.js", "end": [ 1, 11 @@ -241,7 +229,6 @@ 1, 10 ], - "filepath": "anonymous-function.js", "end": [ 1, 11 @@ -260,7 +247,6 @@ 1, 12 ], - "filepath": "anonymous-function.js", "end": [ 1, 13 @@ -271,7 +257,6 @@ 1, 12 ], - "filepath": "anonymous-function.js", "end": [ 1, 13 @@ -290,7 +275,6 @@ 1, 24 ], - "filepath": "anonymous-function.js", "end": [ 1, 25 @@ -301,7 +285,6 @@ 1, 24 ], - "filepath": "anonymous-function.js", "end": [ 1, 25 @@ -320,7 +303,6 @@ 1, 28 ], - "filepath": "anonymous-function.js", "end": [ 1, 29 @@ -331,7 +313,6 @@ 1, 28 ], - "filepath": "anonymous-function.js", "end": [ 1, 29 @@ -349,9 +330,9 @@ "filePaths": [ "anonymous-function.js" ], - "sha1": "17f190c1e1d695127ad44863ac2d576475829a7a", + "sha1": "6fc93b6614e4cfff72463ca12e9987c14fb24c6f", "gitDir": "test/corpus/repos/javascript", - "sha2": "5220b599e5b17fd314a8dc74edca84ba8281599a" + "sha2": "c6ba2db9ae426f80263c615cc53d465d3e20417b" } ,{ "testCaseDescription": "javascript-anonymous-function-delete-replacement-test", @@ -365,7 +346,6 @@ 1, 1 ], - "filepath": "anonymous-function.js", "end": [ 1, 32 @@ -382,7 +362,6 @@ 2, 1 ], - "filepath": "anonymous-function.js", "end": [ 2, 32 @@ -399,7 +378,6 @@ 2, 1 ], - "filepath": "anonymous-function.js", "end": [ 2, 32 @@ -416,9 +394,9 @@ "filePaths": [ "anonymous-function.js" ], - "sha1": "5220b599e5b17fd314a8dc74edca84ba8281599a", + "sha1": "c6ba2db9ae426f80263c615cc53d465d3e20417b", "gitDir": "test/corpus/repos/javascript", - "sha2": "0988f0cf1f9e846e520a14e4dc888a20066ea290" + "sha2": "95ca98c8ae2cc3b0eac592b39529678fbc60cb5e" } ,{ "testCaseDescription": "javascript-anonymous-function-delete-test", @@ -432,7 +410,6 @@ 1, 1 ], - "filepath": "anonymous-function.js", "end": [ 1, 32 @@ -449,9 +426,9 @@ "filePaths": [ "anonymous-function.js" ], - "sha1": "0988f0cf1f9e846e520a14e4dc888a20066ea290", + "sha1": "95ca98c8ae2cc3b0eac592b39529678fbc60cb5e", "gitDir": "test/corpus/repos/javascript", - "sha2": "17e45825eb444ba6321dc4048296cb5e573d413d" + "sha2": "fdc9c77b584391d5efc4ee112d766985422eccc3" } ,{ "testCaseDescription": "javascript-anonymous-function-delete-rest-test", @@ -465,7 +442,6 @@ 1, 1 ], - "filepath": "anonymous-function.js", "end": [ 1, 32 @@ -482,7 +458,7 @@ "filePaths": [ "anonymous-function.js" ], - "sha1": "17e45825eb444ba6321dc4048296cb5e573d413d", + "sha1": "fdc9c77b584391d5efc4ee112d766985422eccc3", "gitDir": "test/corpus/repos/javascript", - "sha2": "9cc9092ea7c2d10872eda86185bbb47582e25811" + "sha2": "d4b2414c028e39dae3876a16e6b0b213320be351" }] diff --git a/test/corpus/diff-summaries/javascript/anonymous-parameterless-function.json b/test/corpus/diff-summaries/javascript/anonymous-parameterless-function.json index b110b1d67..3a11da3ee 100644 --- a/test/corpus/diff-summaries/javascript/anonymous-parameterless-function.json +++ b/test/corpus/diff-summaries/javascript/anonymous-parameterless-function.json @@ -10,7 +10,6 @@ 1, 1 ], - "filepath": "anonymous-parameterless-function.js", "end": [ 1, 28 @@ -27,9 +26,9 @@ "filePaths": [ "anonymous-parameterless-function.js" ], - "sha1": "9cc9092ea7c2d10872eda86185bbb47582e25811", + "sha1": "22b6b91906964ec80192f4d30f12125b99e1cad4", "gitDir": "test/corpus/repos/javascript", - "sha2": "197672a97e83d4934bfbd64977acbeeeb3029f4d" + "sha2": "e41f44ca896e7de4bffa968df9bbf1b1caea1e04" } ,{ "testCaseDescription": "javascript-anonymous-parameterless-function-replacement-insert-test", @@ -43,7 +42,6 @@ 1, 1 ], - "filepath": "anonymous-parameterless-function.js", "end": [ 1, 31 @@ -60,7 +58,6 @@ 2, 1 ], - "filepath": "anonymous-parameterless-function.js", "end": [ 2, 28 @@ -77,9 +74,9 @@ "filePaths": [ "anonymous-parameterless-function.js" ], - "sha1": "197672a97e83d4934bfbd64977acbeeeb3029f4d", + "sha1": "e41f44ca896e7de4bffa968df9bbf1b1caea1e04", "gitDir": "test/corpus/repos/javascript", - "sha2": "e9d899eb8a32fef19e6527564fdeaa799d7861d3" + "sha2": "213068fb89e1381ab15b652ee2f6e16994a6ac16" } ,{ "testCaseDescription": "javascript-anonymous-parameterless-function-delete-insert-test", @@ -94,7 +91,6 @@ 1, 21 ], - "filepath": "anonymous-parameterless-function.js", "end": [ 1, 28 @@ -105,7 +101,6 @@ 1, 21 ], - "filepath": "anonymous-parameterless-function.js", "end": [ 1, 25 @@ -123,9 +118,9 @@ "filePaths": [ "anonymous-parameterless-function.js" ], - "sha1": "e9d899eb8a32fef19e6527564fdeaa799d7861d3", + "sha1": "213068fb89e1381ab15b652ee2f6e16994a6ac16", "gitDir": "test/corpus/repos/javascript", - "sha2": "375ca89d8b6c78f6e58c13caecc05f6e6fb5c086" + "sha2": "e32940ed8b6044088622ac48c96708bac78d9fe2" } ,{ "testCaseDescription": "javascript-anonymous-parameterless-function-replacement-test", @@ -140,7 +135,6 @@ 1, 21 ], - "filepath": "anonymous-parameterless-function.js", "end": [ 1, 25 @@ -151,7 +145,6 @@ 1, 21 ], - "filepath": "anonymous-parameterless-function.js", "end": [ 1, 28 @@ -169,9 +162,9 @@ "filePaths": [ "anonymous-parameterless-function.js" ], - "sha1": "375ca89d8b6c78f6e58c13caecc05f6e6fb5c086", + "sha1": "e32940ed8b6044088622ac48c96708bac78d9fe2", "gitDir": "test/corpus/repos/javascript", - "sha2": "9a74f1d5b3a08c8a13477626bb5e14624a215266" + "sha2": "7ff2f9753b8b8a5c06187ba407bddb72742d4d2b" } ,{ "testCaseDescription": "javascript-anonymous-parameterless-function-delete-replacement-test", @@ -185,7 +178,6 @@ 1, 1 ], - "filepath": "anonymous-parameterless-function.js", "end": [ 1, 31 @@ -202,7 +194,6 @@ 2, 1 ], - "filepath": "anonymous-parameterless-function.js", "end": [ 2, 28 @@ -219,7 +210,6 @@ 2, 1 ], - "filepath": "anonymous-parameterless-function.js", "end": [ 2, 31 @@ -236,9 +226,9 @@ "filePaths": [ "anonymous-parameterless-function.js" ], - "sha1": "9a74f1d5b3a08c8a13477626bb5e14624a215266", + "sha1": "7ff2f9753b8b8a5c06187ba407bddb72742d4d2b", "gitDir": "test/corpus/repos/javascript", - "sha2": "03aa91ccd77862d7a2000366fd907e8a48534fce" + "sha2": "7aff9964814159468da7f26875cf415b3558eee4" } ,{ "testCaseDescription": "javascript-anonymous-parameterless-function-delete-test", @@ -252,7 +242,6 @@ 1, 1 ], - "filepath": "anonymous-parameterless-function.js", "end": [ 1, 28 @@ -269,9 +258,9 @@ "filePaths": [ "anonymous-parameterless-function.js" ], - "sha1": "03aa91ccd77862d7a2000366fd907e8a48534fce", + "sha1": "7aff9964814159468da7f26875cf415b3558eee4", "gitDir": "test/corpus/repos/javascript", - "sha2": "2c667f3b75540474988bd1e2a9268d622de8b12b" + "sha2": "68beb683ce57c3149995ad763f201f4a6836ce2b" } ,{ "testCaseDescription": "javascript-anonymous-parameterless-function-delete-rest-test", @@ -285,7 +274,6 @@ 1, 1 ], - "filepath": "anonymous-parameterless-function.js", "end": [ 1, 31 @@ -302,7 +290,7 @@ "filePaths": [ "anonymous-parameterless-function.js" ], - "sha1": "2c667f3b75540474988bd1e2a9268d622de8b12b", + "sha1": "68beb683ce57c3149995ad763f201f4a6836ce2b", "gitDir": "test/corpus/repos/javascript", - "sha2": "f9fa9489012e03e0ba9e457e290b45d3876c02e6" + "sha2": "b0658b075e567097a50079f320b747eb442b7fe6" }] diff --git a/test/corpus/diff-summaries/javascript/array.json b/test/corpus/diff-summaries/javascript/array.json index 71138bfd9..b19918c46 100644 --- a/test/corpus/diff-summaries/javascript/array.json +++ b/test/corpus/diff-summaries/javascript/array.json @@ -10,7 +10,6 @@ 1, 1 ], - "filepath": "array.js", "end": [ 1, 12 @@ -27,9 +26,9 @@ "filePaths": [ "array.js" ], - "sha1": "b5b3abeccc0703872ec7867eef96c235e5b8c3e6", + "sha1": "2eae8fefa77d6a4d6f762811f764fb0194e0c694", "gitDir": "test/corpus/repos/javascript", - "sha2": "b3800c165955446e2125fca57f25adf6e33cbf8d" + "sha2": "a0220a9f702e60c8fc2a51af41d6c44fb0caef87" } ,{ "testCaseDescription": "javascript-array-replacement-insert-test", @@ -43,7 +42,6 @@ 1, 1 ], - "filepath": "array.js", "end": [ 1, 21 @@ -60,7 +58,6 @@ 2, 1 ], - "filepath": "array.js", "end": [ 2, 12 @@ -77,9 +74,9 @@ "filePaths": [ "array.js" ], - "sha1": "b3800c165955446e2125fca57f25adf6e33cbf8d", + "sha1": "a0220a9f702e60c8fc2a51af41d6c44fb0caef87", "gitDir": "test/corpus/repos/javascript", - "sha2": "08821885b5b37e3810781f68477a2c88041d1a39" + "sha2": "4a15d2534dd78648fdb6d009ac7d300366a3fcd1" } ,{ "testCaseDescription": "javascript-array-delete-insert-test", @@ -93,7 +90,6 @@ 1, 12 ], - "filepath": "array.js", "end": [ 1, 19 @@ -110,9 +106,9 @@ "filePaths": [ "array.js" ], - "sha1": "08821885b5b37e3810781f68477a2c88041d1a39", + "sha1": "4a15d2534dd78648fdb6d009ac7d300366a3fcd1", "gitDir": "test/corpus/repos/javascript", - "sha2": "be2d678e3d03b0709dcbe805940e18b37864343a" + "sha2": "d88be4ec5b1f423eb9e9f43d8bc330029c45d46e" } ,{ "testCaseDescription": "javascript-array-replacement-test", @@ -126,7 +122,6 @@ 1, 12 ], - "filepath": "array.js", "end": [ 1, 19 @@ -143,9 +138,9 @@ "filePaths": [ "array.js" ], - "sha1": "be2d678e3d03b0709dcbe805940e18b37864343a", + "sha1": "d88be4ec5b1f423eb9e9f43d8bc330029c45d46e", "gitDir": "test/corpus/repos/javascript", - "sha2": "d4ccde73868789a623f0a6719ae6deaf5b57cd6f" + "sha2": "b59e1420e44e05650233fd4d4d8de7d800209108" } ,{ "testCaseDescription": "javascript-array-delete-replacement-test", @@ -159,7 +154,6 @@ 1, 1 ], - "filepath": "array.js", "end": [ 1, 21 @@ -176,7 +170,6 @@ 2, 1 ], - "filepath": "array.js", "end": [ 2, 12 @@ -193,7 +186,6 @@ 2, 1 ], - "filepath": "array.js", "end": [ 2, 21 @@ -210,9 +202,9 @@ "filePaths": [ "array.js" ], - "sha1": "d4ccde73868789a623f0a6719ae6deaf5b57cd6f", + "sha1": "b59e1420e44e05650233fd4d4d8de7d800209108", "gitDir": "test/corpus/repos/javascript", - "sha2": "3deca08cc73bbe0e68ea110b1e03fd4abec861bf" + "sha2": "793c9c44d26a5d2cf79c81a10ac7efdba52feb3a" } ,{ "testCaseDescription": "javascript-array-delete-test", @@ -226,7 +218,6 @@ 1, 1 ], - "filepath": "array.js", "end": [ 1, 12 @@ -243,9 +234,9 @@ "filePaths": [ "array.js" ], - "sha1": "3deca08cc73bbe0e68ea110b1e03fd4abec861bf", + "sha1": "793c9c44d26a5d2cf79c81a10ac7efdba52feb3a", "gitDir": "test/corpus/repos/javascript", - "sha2": "dbef93d84b0dc6b7ad858bc840e70c34dbbbea84" + "sha2": "c618daa36f536027c9d7f6e46a90ec22076fdcbf" } ,{ "testCaseDescription": "javascript-array-delete-rest-test", @@ -259,7 +250,6 @@ 1, 1 ], - "filepath": "array.js", "end": [ 1, 21 @@ -276,7 +266,7 @@ "filePaths": [ "array.js" ], - "sha1": "dbef93d84b0dc6b7ad858bc840e70c34dbbbea84", + "sha1": "c618daa36f536027c9d7f6e46a90ec22076fdcbf", "gitDir": "test/corpus/repos/javascript", - "sha2": "8eef7adcdbe1c08c7b39e24ab94c0aa76c2169dc" + "sha2": "1a2d64688174370f61c0962a2cd96be5f1758ccc" }] diff --git a/test/corpus/diff-summaries/javascript/arrow-function.json b/test/corpus/diff-summaries/javascript/arrow-function.json index 29a90590a..2b6fdaf91 100644 --- a/test/corpus/diff-summaries/javascript/arrow-function.json +++ b/test/corpus/diff-summaries/javascript/arrow-function.json @@ -10,7 +10,6 @@ 1, 1 ], - "filepath": "arrow-function.js", "end": [ 1, 24 @@ -27,9 +26,9 @@ "filePaths": [ "arrow-function.js" ], - "sha1": "15ff2677dbf6ef4e724df21936b1dec373b4c087", + "sha1": "1cb91e98d1764fe8fb5c2a7798c9173523abdb1b", "gitDir": "test/corpus/repos/javascript", - "sha2": "6c285606ff4e7906dd63ae09d70e6de2664cde79" + "sha2": "cabe717d9de437bbcf599b358c40bd1a9f7497c5" } ,{ "testCaseDescription": "javascript-arrow-function-replacement-insert-test", @@ -43,7 +42,6 @@ 1, 1 ], - "filepath": "arrow-function.js", "end": [ 1, 24 @@ -60,7 +58,6 @@ 2, 1 ], - "filepath": "arrow-function.js", "end": [ 2, 24 @@ -77,9 +74,9 @@ "filePaths": [ "arrow-function.js" ], - "sha1": "6c285606ff4e7906dd63ae09d70e6de2664cde79", + "sha1": "cabe717d9de437bbcf599b358c40bd1a9f7497c5", "gitDir": "test/corpus/repos/javascript", - "sha2": "5bbcfd065e3917b0302fdbc15cda5fab2f8cf9b3" + "sha2": "81833f1dfc5306bdf83101de4a514162c004f133" } ,{ "testCaseDescription": "javascript-arrow-function-delete-insert-test", @@ -94,7 +91,6 @@ 1, 20 ], - "filepath": "arrow-function.js", "end": [ 1, 21 @@ -105,7 +101,6 @@ 1, 20 ], - "filepath": "arrow-function.js", "end": [ 1, 21 @@ -123,9 +118,9 @@ "filePaths": [ "arrow-function.js" ], - "sha1": "5bbcfd065e3917b0302fdbc15cda5fab2f8cf9b3", + "sha1": "81833f1dfc5306bdf83101de4a514162c004f133", "gitDir": "test/corpus/repos/javascript", - "sha2": "01c89dedc801d910448f2fccc4c199f2ceb3e525" + "sha2": "1477c3eb5d6b3fb17e658851e597548a27e9aee5" } ,{ "testCaseDescription": "javascript-arrow-function-replacement-test", @@ -140,7 +135,6 @@ 1, 20 ], - "filepath": "arrow-function.js", "end": [ 1, 21 @@ -151,7 +145,6 @@ 1, 20 ], - "filepath": "arrow-function.js", "end": [ 1, 21 @@ -169,9 +162,9 @@ "filePaths": [ "arrow-function.js" ], - "sha1": "01c89dedc801d910448f2fccc4c199f2ceb3e525", + "sha1": "1477c3eb5d6b3fb17e658851e597548a27e9aee5", "gitDir": "test/corpus/repos/javascript", - "sha2": "053a09f7e19214d7ea75ccf77313da71c8e163db" + "sha2": "792510a28547ef00fb3f427f0588a350070b78c8" } ,{ "testCaseDescription": "javascript-arrow-function-delete-replacement-test", @@ -185,7 +178,6 @@ 1, 1 ], - "filepath": "arrow-function.js", "end": [ 1, 24 @@ -202,7 +194,6 @@ 2, 1 ], - "filepath": "arrow-function.js", "end": [ 2, 24 @@ -219,7 +210,6 @@ 2, 1 ], - "filepath": "arrow-function.js", "end": [ 2, 24 @@ -236,9 +226,9 @@ "filePaths": [ "arrow-function.js" ], - "sha1": "053a09f7e19214d7ea75ccf77313da71c8e163db", + "sha1": "792510a28547ef00fb3f427f0588a350070b78c8", "gitDir": "test/corpus/repos/javascript", - "sha2": "20adb0c98028b1baa8115b40036e39b8f437561a" + "sha2": "43d4dec7b3f7190611127a9184ba1b8c7ef95581" } ,{ "testCaseDescription": "javascript-arrow-function-delete-test", @@ -252,7 +242,6 @@ 1, 1 ], - "filepath": "arrow-function.js", "end": [ 1, 24 @@ -269,9 +258,9 @@ "filePaths": [ "arrow-function.js" ], - "sha1": "20adb0c98028b1baa8115b40036e39b8f437561a", + "sha1": "43d4dec7b3f7190611127a9184ba1b8c7ef95581", "gitDir": "test/corpus/repos/javascript", - "sha2": "cb5d85e27b0dad945694e07131ae9d9b09dd0c09" + "sha2": "614d74c2b78fee8293f461aa293c56622049c72b" } ,{ "testCaseDescription": "javascript-arrow-function-delete-rest-test", @@ -285,7 +274,6 @@ 1, 1 ], - "filepath": "arrow-function.js", "end": [ 1, 24 @@ -302,7 +290,7 @@ "filePaths": [ "arrow-function.js" ], - "sha1": "cb5d85e27b0dad945694e07131ae9d9b09dd0c09", + "sha1": "614d74c2b78fee8293f461aa293c56622049c72b", "gitDir": "test/corpus/repos/javascript", - "sha2": "64732c38069cc70ee3bea66306d966d902444b68" + "sha2": "9a88415672c0d83242b643e750b77540103e14c1" }] diff --git a/test/corpus/diff-summaries/javascript/assignment.json b/test/corpus/diff-summaries/javascript/assignment.json index bf56f2d1e..b67a967a8 100644 --- a/test/corpus/diff-summaries/javascript/assignment.json +++ b/test/corpus/diff-summaries/javascript/assignment.json @@ -10,7 +10,6 @@ 1, 1 ], - "filepath": "assignment.js", "end": [ 1, 6 @@ -27,9 +26,9 @@ "filePaths": [ "assignment.js" ], - "sha1": "0ee5df2573a8439ceee6c04faf15813932be3ad0", + "sha1": "e1b8eb2bcd67f643f76a7eb820f49a2ef4f1774c", "gitDir": "test/corpus/repos/javascript", - "sha2": "da0e92c5c2d634371ae323ac72438223319cf76c" + "sha2": "3a7df001a06d312b1befb24699e3f60a41e07c09" } ,{ "testCaseDescription": "javascript-assignment-replacement-insert-test", @@ -43,7 +42,6 @@ 1, 1 ], - "filepath": "assignment.js", "end": [ 1, 6 @@ -60,7 +58,6 @@ 2, 1 ], - "filepath": "assignment.js", "end": [ 2, 6 @@ -77,9 +74,9 @@ "filePaths": [ "assignment.js" ], - "sha1": "da0e92c5c2d634371ae323ac72438223319cf76c", + "sha1": "3a7df001a06d312b1befb24699e3f60a41e07c09", "gitDir": "test/corpus/repos/javascript", - "sha2": "8d696d6419a22c606acbc24717a78ad28167e38e" + "sha2": "6142fd5f7cc7d6882b4d2682beb6ab487f37221f" } ,{ "testCaseDescription": "javascript-assignment-delete-insert-test", @@ -94,7 +91,6 @@ 1, 5 ], - "filepath": "assignment.js", "end": [ 1, 6 @@ -105,7 +101,6 @@ 1, 5 ], - "filepath": "assignment.js", "end": [ 1, 6 @@ -123,9 +118,9 @@ "filePaths": [ "assignment.js" ], - "sha1": "8d696d6419a22c606acbc24717a78ad28167e38e", + "sha1": "6142fd5f7cc7d6882b4d2682beb6ab487f37221f", "gitDir": "test/corpus/repos/javascript", - "sha2": "6ac72e1d2736cbc8e0d562a8f5d1f21b5e0decd2" + "sha2": "ccd4b8841a4c1ac1e93e7b6937b085ca9c589f45" } ,{ "testCaseDescription": "javascript-assignment-replacement-test", @@ -140,7 +135,6 @@ 1, 5 ], - "filepath": "assignment.js", "end": [ 1, 6 @@ -151,7 +145,6 @@ 1, 5 ], - "filepath": "assignment.js", "end": [ 1, 6 @@ -169,9 +162,9 @@ "filePaths": [ "assignment.js" ], - "sha1": "6ac72e1d2736cbc8e0d562a8f5d1f21b5e0decd2", + "sha1": "ccd4b8841a4c1ac1e93e7b6937b085ca9c589f45", "gitDir": "test/corpus/repos/javascript", - "sha2": "a188b4a762653a4bf556d9d9070d978dee3f87c8" + "sha2": "e50c3b804fe956a8d66c615ce341d23949b1e0bc" } ,{ "testCaseDescription": "javascript-assignment-delete-replacement-test", @@ -185,7 +178,6 @@ 1, 1 ], - "filepath": "assignment.js", "end": [ 1, 6 @@ -202,7 +194,6 @@ 2, 1 ], - "filepath": "assignment.js", "end": [ 2, 6 @@ -219,7 +210,6 @@ 2, 1 ], - "filepath": "assignment.js", "end": [ 2, 6 @@ -236,9 +226,9 @@ "filePaths": [ "assignment.js" ], - "sha1": "a188b4a762653a4bf556d9d9070d978dee3f87c8", + "sha1": "e50c3b804fe956a8d66c615ce341d23949b1e0bc", "gitDir": "test/corpus/repos/javascript", - "sha2": "b5d95b98b09c3ad83bdd6baded131e1a0bbbcd3b" + "sha2": "9a82a708b3f1e537ea6580f22e1c61a39c0e56f2" } ,{ "testCaseDescription": "javascript-assignment-delete-test", @@ -252,7 +242,6 @@ 1, 1 ], - "filepath": "assignment.js", "end": [ 1, 6 @@ -269,9 +258,9 @@ "filePaths": [ "assignment.js" ], - "sha1": "b5d95b98b09c3ad83bdd6baded131e1a0bbbcd3b", + "sha1": "9a82a708b3f1e537ea6580f22e1c61a39c0e56f2", "gitDir": "test/corpus/repos/javascript", - "sha2": "544ea82481b53de3579e1df05aeef7495a9ba80f" + "sha2": "8ca532d1c838722ab652073a5052a0bb58bba456" } ,{ "testCaseDescription": "javascript-assignment-delete-rest-test", @@ -285,7 +274,6 @@ 1, 1 ], - "filepath": "assignment.js", "end": [ 1, 6 @@ -302,7 +290,7 @@ "filePaths": [ "assignment.js" ], - "sha1": "544ea82481b53de3579e1df05aeef7495a9ba80f", + "sha1": "8ca532d1c838722ab652073a5052a0bb58bba456", "gitDir": "test/corpus/repos/javascript", - "sha2": "515ac3ce664c0458a2daec58a009a959898bebfc" + "sha2": "db6bbfe82747173a73c33bab9da91003e1fe0634" }] diff --git a/test/corpus/diff-summaries/javascript/bitwise-operator.json b/test/corpus/diff-summaries/javascript/bitwise-operator.json index 52fdc1f4d..5f9ca08e4 100644 --- a/test/corpus/diff-summaries/javascript/bitwise-operator.json +++ b/test/corpus/diff-summaries/javascript/bitwise-operator.json @@ -10,7 +10,6 @@ 1, 1 ], - "filepath": "bitwise-operator.js", "end": [ 1, 7 @@ -27,9 +26,9 @@ "filePaths": [ "bitwise-operator.js" ], - "sha1": "e4a9c13399b50a6b4833a5804fb4537e5869f9ca", + "sha1": "234b7e78605626501d422c4431c88b50e9e19c3f", "gitDir": "test/corpus/repos/javascript", - "sha2": "f9f0b821f7b95ceaeb9cfe60b02745b3269984c4" + "sha2": "12ac8e040299cccf6336a3001138af774f8fd5de" } ,{ "testCaseDescription": "javascript-bitwise-operator-replacement-insert-test", @@ -43,7 +42,6 @@ 1, 1 ], - "filepath": "bitwise-operator.js", "end": [ 1, 7 @@ -60,7 +58,6 @@ 2, 1 ], - "filepath": "bitwise-operator.js", "end": [ 2, 7 @@ -77,9 +74,9 @@ "filePaths": [ "bitwise-operator.js" ], - "sha1": "f9f0b821f7b95ceaeb9cfe60b02745b3269984c4", + "sha1": "12ac8e040299cccf6336a3001138af774f8fd5de", "gitDir": "test/corpus/repos/javascript", - "sha2": "56542f8dbf7a335a464d5b2f8f53d1b0bc76d8ef" + "sha2": "28a35690a7bb5269f65ed3366cf19eed19b04eb3" } ,{ "testCaseDescription": "javascript-bitwise-operator-delete-insert-test", @@ -94,7 +91,6 @@ 1, 6 ], - "filepath": "bitwise-operator.js", "end": [ 1, 7 @@ -105,7 +101,6 @@ 1, 6 ], - "filepath": "bitwise-operator.js", "end": [ 1, 7 @@ -123,9 +118,9 @@ "filePaths": [ "bitwise-operator.js" ], - "sha1": "56542f8dbf7a335a464d5b2f8f53d1b0bc76d8ef", + "sha1": "28a35690a7bb5269f65ed3366cf19eed19b04eb3", "gitDir": "test/corpus/repos/javascript", - "sha2": "8c28c1de4171e57397880fd4288f9d57ecd3040b" + "sha2": "caf88ce357d00963864665477ea0261115ba0e82" } ,{ "testCaseDescription": "javascript-bitwise-operator-replacement-test", @@ -140,7 +135,6 @@ 1, 6 ], - "filepath": "bitwise-operator.js", "end": [ 1, 7 @@ -151,7 +145,6 @@ 1, 6 ], - "filepath": "bitwise-operator.js", "end": [ 1, 7 @@ -169,9 +162,9 @@ "filePaths": [ "bitwise-operator.js" ], - "sha1": "8c28c1de4171e57397880fd4288f9d57ecd3040b", + "sha1": "caf88ce357d00963864665477ea0261115ba0e82", "gitDir": "test/corpus/repos/javascript", - "sha2": "a9a7be019acc945b16ddbb08ae49891eb59419d8" + "sha2": "04d9d80788f8ec45b6a7fd916aebdb66940d9516" } ,{ "testCaseDescription": "javascript-bitwise-operator-delete-replacement-test", @@ -185,7 +178,6 @@ 1, 1 ], - "filepath": "bitwise-operator.js", "end": [ 1, 7 @@ -202,7 +194,6 @@ 2, 1 ], - "filepath": "bitwise-operator.js", "end": [ 2, 7 @@ -219,7 +210,6 @@ 2, 1 ], - "filepath": "bitwise-operator.js", "end": [ 2, 7 @@ -236,9 +226,9 @@ "filePaths": [ "bitwise-operator.js" ], - "sha1": "a9a7be019acc945b16ddbb08ae49891eb59419d8", + "sha1": "04d9d80788f8ec45b6a7fd916aebdb66940d9516", "gitDir": "test/corpus/repos/javascript", - "sha2": "fa1a257fd537600aad9a30ded1e68220c59efba6" + "sha2": "3b00668eb968387c144b63f111afade1814aa3a7" } ,{ "testCaseDescription": "javascript-bitwise-operator-delete-test", @@ -252,7 +242,6 @@ 1, 1 ], - "filepath": "bitwise-operator.js", "end": [ 1, 7 @@ -269,9 +258,9 @@ "filePaths": [ "bitwise-operator.js" ], - "sha1": "fa1a257fd537600aad9a30ded1e68220c59efba6", + "sha1": "3b00668eb968387c144b63f111afade1814aa3a7", "gitDir": "test/corpus/repos/javascript", - "sha2": "8e073e4a070ff6b184c4bbd420d843b617930e26" + "sha2": "ff907e0620f083698334862f24d9269d1ac43f89" } ,{ "testCaseDescription": "javascript-bitwise-operator-delete-rest-test", @@ -285,7 +274,6 @@ 1, 1 ], - "filepath": "bitwise-operator.js", "end": [ 1, 7 @@ -302,7 +290,7 @@ "filePaths": [ "bitwise-operator.js" ], - "sha1": "8e073e4a070ff6b184c4bbd420d843b617930e26", + "sha1": "ff907e0620f083698334862f24d9269d1ac43f89", "gitDir": "test/corpus/repos/javascript", - "sha2": "aa8e5d0cc9ed22261dd69958752f86537aa464da" + "sha2": "d3b83b525c7e185792b6284b8c0b23dbce07fa7e" }] diff --git a/test/corpus/diff-summaries/javascript/boolean-operator.json b/test/corpus/diff-summaries/javascript/boolean-operator.json index 74912be7f..e719fedf8 100644 --- a/test/corpus/diff-summaries/javascript/boolean-operator.json +++ b/test/corpus/diff-summaries/javascript/boolean-operator.json @@ -10,7 +10,6 @@ 1, 1 ], - "filepath": "boolean-operator.js", "end": [ 1, 7 @@ -27,9 +26,9 @@ "filePaths": [ "boolean-operator.js" ], - "sha1": "5e5d08f5cc6ce83a5663d10215511b13bddd76e3", + "sha1": "81b6988e6543884fa895f07a06283ca091f49afb", "gitDir": "test/corpus/repos/javascript", - "sha2": "63101d962f8cc10377266e9c48e69153b10c278d" + "sha2": "77c4304f467e33c59a93a93a9cd1e5e1ebf7809b" } ,{ "testCaseDescription": "javascript-boolean-operator-replacement-insert-test", @@ -43,7 +42,6 @@ 1, 1 ], - "filepath": "boolean-operator.js", "end": [ 1, 7 @@ -60,7 +58,6 @@ 2, 1 ], - "filepath": "boolean-operator.js", "end": [ 2, 7 @@ -77,9 +74,9 @@ "filePaths": [ "boolean-operator.js" ], - "sha1": "63101d962f8cc10377266e9c48e69153b10c278d", + "sha1": "77c4304f467e33c59a93a93a9cd1e5e1ebf7809b", "gitDir": "test/corpus/repos/javascript", - "sha2": "a4bf80ff4b2c06fe7ce93576f0f0017b2303cd0e" + "sha2": "04da46027e8e42577cf51f664a641af1473ea21b" } ,{ "testCaseDescription": "javascript-boolean-operator-delete-insert-test", @@ -90,9 +87,9 @@ "filePaths": [ "boolean-operator.js" ], - "sha1": "a4bf80ff4b2c06fe7ce93576f0f0017b2303cd0e", + "sha1": "04da46027e8e42577cf51f664a641af1473ea21b", "gitDir": "test/corpus/repos/javascript", - "sha2": "b99a56aa9e95e7a0c982c1ff55d40cb8ad6671a7" + "sha2": "2144b6fdcd32aa805f9a548e8c774d4b0d78211e" } ,{ "testCaseDescription": "javascript-boolean-operator-replacement-test", @@ -103,9 +100,9 @@ "filePaths": [ "boolean-operator.js" ], - "sha1": "b99a56aa9e95e7a0c982c1ff55d40cb8ad6671a7", + "sha1": "2144b6fdcd32aa805f9a548e8c774d4b0d78211e", "gitDir": "test/corpus/repos/javascript", - "sha2": "afb55614792566d0fde75e057c4a1d6045e2edd6" + "sha2": "cab2550c31bd9e3b9ca409155d875b9c34a96396" } ,{ "testCaseDescription": "javascript-boolean-operator-delete-replacement-test", @@ -119,7 +116,6 @@ 1, 1 ], - "filepath": "boolean-operator.js", "end": [ 1, 7 @@ -136,9 +132,9 @@ "filePaths": [ "boolean-operator.js" ], - "sha1": "afb55614792566d0fde75e057c4a1d6045e2edd6", + "sha1": "cab2550c31bd9e3b9ca409155d875b9c34a96396", "gitDir": "test/corpus/repos/javascript", - "sha2": "8d00addb72a904326e16449b9fe27e81fffb201a" + "sha2": "d255d477f62bb73de5039084ffd0afecbb5d500c" } ,{ "testCaseDescription": "javascript-boolean-operator-delete-test", @@ -152,7 +148,6 @@ 1, 1 ], - "filepath": "boolean-operator.js", "end": [ 1, 7 @@ -169,9 +164,9 @@ "filePaths": [ "boolean-operator.js" ], - "sha1": "8d00addb72a904326e16449b9fe27e81fffb201a", + "sha1": "d255d477f62bb73de5039084ffd0afecbb5d500c", "gitDir": "test/corpus/repos/javascript", - "sha2": "83067fcd7b567e23d27471d4693ebc69b1067b4e" + "sha2": "ec883a059891f976a9050e6b9100135dbe5cabee" } ,{ "testCaseDescription": "javascript-boolean-operator-delete-rest-test", @@ -185,7 +180,6 @@ 1, 1 ], - "filepath": "boolean-operator.js", "end": [ 1, 7 @@ -202,7 +196,7 @@ "filePaths": [ "boolean-operator.js" ], - "sha1": "83067fcd7b567e23d27471d4693ebc69b1067b4e", + "sha1": "ec883a059891f976a9050e6b9100135dbe5cabee", "gitDir": "test/corpus/repos/javascript", - "sha2": "e4a9c13399b50a6b4833a5804fb4537e5869f9ca" + "sha2": "35c3545e63b37ef12af64bbc9bafaf502a95db29" }] diff --git a/test/corpus/diff-summaries/javascript/chained-callbacks.json b/test/corpus/diff-summaries/javascript/chained-callbacks.json index 67877a499..e72a6b0d5 100644 --- a/test/corpus/diff-summaries/javascript/chained-callbacks.json +++ b/test/corpus/diff-summaries/javascript/chained-callbacks.json @@ -10,7 +10,6 @@ 1, 1 ], - "filepath": "chained-callbacks.js", "end": [ 1, 39 @@ -27,9 +26,9 @@ "filePaths": [ "chained-callbacks.js" ], - "sha1": "92d3d86c59db44e6c646c1b8ba61bf650f0ac5d4", + "sha1": "9805a53f9fb8f6cd969d07ef2eeec2250fd12d04", "gitDir": "test/corpus/repos/javascript", - "sha2": "16b8043a700cdf894ae3be1fc8f6e39428b596fe" + "sha2": "95c5995bf1d9fd3208a872cd598032cece4a8bac" } ,{ "testCaseDescription": "javascript-chained-callbacks-replacement-insert-test", @@ -43,7 +42,6 @@ 1, 1 ], - "filepath": "chained-callbacks.js", "end": [ 1, 42 @@ -60,7 +58,6 @@ 2, 1 ], - "filepath": "chained-callbacks.js", "end": [ 2, 39 @@ -77,9 +74,9 @@ "filePaths": [ "chained-callbacks.js" ], - "sha1": "16b8043a700cdf894ae3be1fc8f6e39428b596fe", + "sha1": "95c5995bf1d9fd3208a872cd598032cece4a8bac", "gitDir": "test/corpus/repos/javascript", - "sha2": "0be3fdde3855a989678bfcf69fb130005e3a543e" + "sha2": "4b97bdc99bdd0ff6bb811ab647482f93444203d7" } ,{ "testCaseDescription": "javascript-chained-callbacks-delete-insert-test", @@ -94,7 +91,6 @@ 1, 6 ], - "filepath": "chained-callbacks.js", "end": [ 1, 12 @@ -105,7 +101,6 @@ 1, 6 ], - "filepath": "chained-callbacks.js", "end": [ 1, 9 @@ -124,7 +119,6 @@ 1, 35 ], - "filepath": "chained-callbacks.js", "end": [ 1, 36 @@ -135,7 +129,6 @@ 1, 32 ], - "filepath": "chained-callbacks.js", "end": [ 1, 33 @@ -154,7 +147,6 @@ 1, 37 ], - "filepath": "chained-callbacks.js", "end": [ 1, 38 @@ -165,7 +157,6 @@ 1, 34 ], - "filepath": "chained-callbacks.js", "end": [ 1, 35 @@ -183,9 +174,9 @@ "filePaths": [ "chained-callbacks.js" ], - "sha1": "0be3fdde3855a989678bfcf69fb130005e3a543e", + "sha1": "4b97bdc99bdd0ff6bb811ab647482f93444203d7", "gitDir": "test/corpus/repos/javascript", - "sha2": "d8793e0b94c7e48f206f852d5d2d0cc39709ef24" + "sha2": "e925672c3d607a47dd28821be89fc163547f317a" } ,{ "testCaseDescription": "javascript-chained-callbacks-replacement-test", @@ -200,7 +191,6 @@ 1, 6 ], - "filepath": "chained-callbacks.js", "end": [ 1, 9 @@ -211,7 +201,6 @@ 1, 6 ], - "filepath": "chained-callbacks.js", "end": [ 1, 12 @@ -230,7 +219,6 @@ 1, 32 ], - "filepath": "chained-callbacks.js", "end": [ 1, 33 @@ -241,7 +229,6 @@ 1, 35 ], - "filepath": "chained-callbacks.js", "end": [ 1, 36 @@ -260,7 +247,6 @@ 1, 34 ], - "filepath": "chained-callbacks.js", "end": [ 1, 35 @@ -271,7 +257,6 @@ 1, 37 ], - "filepath": "chained-callbacks.js", "end": [ 1, 38 @@ -289,9 +274,9 @@ "filePaths": [ "chained-callbacks.js" ], - "sha1": "d8793e0b94c7e48f206f852d5d2d0cc39709ef24", + "sha1": "e925672c3d607a47dd28821be89fc163547f317a", "gitDir": "test/corpus/repos/javascript", - "sha2": "ba2894f2b600705cce62c432e9fbcb0055ed7809" + "sha2": "8f1ee6a59a82c0aa8e951dd4b2865f8105c4b9e4" } ,{ "testCaseDescription": "javascript-chained-callbacks-delete-replacement-test", @@ -305,7 +290,6 @@ 1, 1 ], - "filepath": "chained-callbacks.js", "end": [ 1, 42 @@ -322,7 +306,6 @@ 2, 1 ], - "filepath": "chained-callbacks.js", "end": [ 2, 39 @@ -339,7 +322,6 @@ 2, 1 ], - "filepath": "chained-callbacks.js", "end": [ 2, 42 @@ -356,9 +338,9 @@ "filePaths": [ "chained-callbacks.js" ], - "sha1": "ba2894f2b600705cce62c432e9fbcb0055ed7809", + "sha1": "8f1ee6a59a82c0aa8e951dd4b2865f8105c4b9e4", "gitDir": "test/corpus/repos/javascript", - "sha2": "65220722c5b3fa4ce786dee81ae090aa49effa02" + "sha2": "fca34a1451c2b8708049c924710c971127d9efc0" } ,{ "testCaseDescription": "javascript-chained-callbacks-delete-test", @@ -372,7 +354,6 @@ 1, 1 ], - "filepath": "chained-callbacks.js", "end": [ 1, 39 @@ -389,9 +370,9 @@ "filePaths": [ "chained-callbacks.js" ], - "sha1": "65220722c5b3fa4ce786dee81ae090aa49effa02", + "sha1": "fca34a1451c2b8708049c924710c971127d9efc0", "gitDir": "test/corpus/repos/javascript", - "sha2": "e0a158e1f8b035c1f6833be47cc4f21030f9f4c7" + "sha2": "820ff2e5b738c2a4c6b67bb00137825db09eaf54" } ,{ "testCaseDescription": "javascript-chained-callbacks-delete-rest-test", @@ -405,7 +386,6 @@ 1, 1 ], - "filepath": "chained-callbacks.js", "end": [ 1, 42 @@ -422,7 +402,7 @@ "filePaths": [ "chained-callbacks.js" ], - "sha1": "e0a158e1f8b035c1f6833be47cc4f21030f9f4c7", + "sha1": "820ff2e5b738c2a4c6b67bb00137825db09eaf54", "gitDir": "test/corpus/repos/javascript", - "sha2": "4eca89a41a58f273d4b0819fde38f18c1f8e8021" + "sha2": "d1e7f56a86f0ad76a52e486579b7319c4da64d38" }] diff --git a/test/corpus/diff-summaries/javascript/chained-property-access.json b/test/corpus/diff-summaries/javascript/chained-property-access.json index 1c9edc2de..552a4adb1 100644 --- a/test/corpus/diff-summaries/javascript/chained-property-access.json +++ b/test/corpus/diff-summaries/javascript/chained-property-access.json @@ -10,7 +10,6 @@ 1, 1 ], - "filepath": "chained-property-access.js", "end": [ 2, 1 @@ -27,9 +26,9 @@ "filePaths": [ "chained-property-access.js" ], - "sha1": "80490123a60bcb2826ae89e9baaba5b8b9517e14", + "sha1": "1e0859960bebec7c346191192b74d0625ae68f54", "gitDir": "test/corpus/repos/javascript", - "sha2": "8818771491d7cdd2bfc65bc138bed22860cdd953" + "sha2": "607fd3f3d13592c0bf22ffd2ad1395c759a9ac9c" } ,{ "testCaseDescription": "javascript-chained-property-access-replacement-insert-test", @@ -43,7 +42,6 @@ 1, 1 ], - "filepath": "chained-property-access.js", "end": [ 2, 1 @@ -60,7 +58,6 @@ 2, 1 ], - "filepath": "chained-property-access.js", "end": [ 3, 1 @@ -77,9 +74,9 @@ "filePaths": [ "chained-property-access.js" ], - "sha1": "8818771491d7cdd2bfc65bc138bed22860cdd953", + "sha1": "607fd3f3d13592c0bf22ffd2ad1395c759a9ac9c", "gitDir": "test/corpus/repos/javascript", - "sha2": "ff20c85dc5872809f74fcd00b51a941839070694" + "sha2": "bfbb22ba2d321e4b458857e6e6e053d387bd744e" } ,{ "testCaseDescription": "javascript-chained-property-access-delete-insert-test", @@ -94,7 +91,6 @@ 1, 33 ], - "filepath": "chained-property-access.js", "end": [ 1, 43 @@ -105,7 +101,6 @@ 1, 33 ], - "filepath": "chained-property-access.js", "end": [ 1, 41 @@ -124,7 +119,6 @@ 1, 60 ], - "filepath": "chained-property-access.js", "end": [ 1, 70 @@ -135,7 +129,6 @@ 1, 58 ], - "filepath": "chained-property-access.js", "end": [ 1, 66 @@ -153,9 +146,9 @@ "filePaths": [ "chained-property-access.js" ], - "sha1": "ff20c85dc5872809f74fcd00b51a941839070694", + "sha1": "bfbb22ba2d321e4b458857e6e6e053d387bd744e", "gitDir": "test/corpus/repos/javascript", - "sha2": "7b6314f109e776aaffa52d289048010dafe2e4b0" + "sha2": "f8c579de58d41201e75fc6ef898bb19612485b74" } ,{ "testCaseDescription": "javascript-chained-property-access-replacement-test", @@ -170,7 +163,6 @@ 1, 33 ], - "filepath": "chained-property-access.js", "end": [ 1, 41 @@ -181,7 +173,6 @@ 1, 33 ], - "filepath": "chained-property-access.js", "end": [ 1, 43 @@ -200,7 +191,6 @@ 1, 58 ], - "filepath": "chained-property-access.js", "end": [ 1, 66 @@ -211,7 +201,6 @@ 1, 60 ], - "filepath": "chained-property-access.js", "end": [ 1, 70 @@ -229,9 +218,9 @@ "filePaths": [ "chained-property-access.js" ], - "sha1": "7b6314f109e776aaffa52d289048010dafe2e4b0", + "sha1": "f8c579de58d41201e75fc6ef898bb19612485b74", "gitDir": "test/corpus/repos/javascript", - "sha2": "62cca7857435d41ce759d374f2577726e10fcde8" + "sha2": "500274ded0883d60ed5e9137cde2a9c5ec057646" } ,{ "testCaseDescription": "javascript-chained-property-access-delete-replacement-test", @@ -245,7 +234,6 @@ 1, 1 ], - "filepath": "chained-property-access.js", "end": [ 2, 1 @@ -262,7 +250,6 @@ 2, 1 ], - "filepath": "chained-property-access.js", "end": [ 3, 1 @@ -279,7 +266,6 @@ 2, 1 ], - "filepath": "chained-property-access.js", "end": [ 3, 1 @@ -296,9 +282,9 @@ "filePaths": [ "chained-property-access.js" ], - "sha1": "62cca7857435d41ce759d374f2577726e10fcde8", + "sha1": "500274ded0883d60ed5e9137cde2a9c5ec057646", "gitDir": "test/corpus/repos/javascript", - "sha2": "e35f94123a9744181d251ae9ccd2f3a569befdea" + "sha2": "c4b82844d26c3b49ff4ad0bb6908e89ff58e87f1" } ,{ "testCaseDescription": "javascript-chained-property-access-delete-test", @@ -312,7 +298,6 @@ 1, 1 ], - "filepath": "chained-property-access.js", "end": [ 2, 1 @@ -329,9 +314,9 @@ "filePaths": [ "chained-property-access.js" ], - "sha1": "e35f94123a9744181d251ae9ccd2f3a569befdea", + "sha1": "c4b82844d26c3b49ff4ad0bb6908e89ff58e87f1", "gitDir": "test/corpus/repos/javascript", - "sha2": "05e0b2c40eaa24629f4958dc34d4b8b7632e2d26" + "sha2": "1a601394ffbc287695bbf2b63d5e85d1b9ba66dd" } ,{ "testCaseDescription": "javascript-chained-property-access-delete-rest-test", @@ -345,7 +330,6 @@ 1, 1 ], - "filepath": "chained-property-access.js", "end": [ 2, 1 @@ -362,7 +346,7 @@ "filePaths": [ "chained-property-access.js" ], - "sha1": "05e0b2c40eaa24629f4958dc34d4b8b7632e2d26", + "sha1": "1a601394ffbc287695bbf2b63d5e85d1b9ba66dd", "gitDir": "test/corpus/repos/javascript", - "sha2": "92d3d86c59db44e6c646c1b8ba61bf650f0ac5d4" + "sha2": "e2ad5d3fafb90d720b3c803892c914529086848a" }] diff --git a/test/corpus/diff-summaries/javascript/class.json b/test/corpus/diff-summaries/javascript/class.json index b9c7de4f3..0f7a99db5 100644 --- a/test/corpus/diff-summaries/javascript/class.json +++ b/test/corpus/diff-summaries/javascript/class.json @@ -10,7 +10,6 @@ 1, 1 ], - "filepath": "class.js", "end": [ 1, 87 @@ -27,9 +26,9 @@ "filePaths": [ "class.js" ], - "sha1": "70901cee54467ad046311d039d1dca528a0a7111", + "sha1": "19a0f5ed94699f179f887755095f2b6bd484ba1b", "gitDir": "test/corpus/repos/javascript", - "sha2": "513cdfde7defde2ae32eddbbc32f3697be698d82" + "sha2": "f83f2944c43ab1c3a311114018bc9def1a08ef2c" } ,{ "testCaseDescription": "javascript-class-replacement-insert-test", @@ -43,7 +42,6 @@ 1, 1 ], - "filepath": "class.js", "end": [ 1, 85 @@ -60,7 +58,6 @@ 2, 1 ], - "filepath": "class.js", "end": [ 2, 87 @@ -77,9 +74,9 @@ "filePaths": [ "class.js" ], - "sha1": "513cdfde7defde2ae32eddbbc32f3697be698d82", + "sha1": "f83f2944c43ab1c3a311114018bc9def1a08ef2c", "gitDir": "test/corpus/repos/javascript", - "sha2": "c787d2802f7dfeeff51937b38139a8938e04c56c" + "sha2": "9c20b127c193a62b80eda6b277bb7a909e7b761a" } ,{ "testCaseDescription": "javascript-class-delete-insert-test", @@ -94,7 +91,6 @@ 1, 20 ], - "filepath": "class.js", "end": [ 1, 23 @@ -105,7 +101,6 @@ 1, 20 ], - "filepath": "class.js", "end": [ 1, 23 @@ -124,7 +119,6 @@ 1, 42 ], - "filepath": "class.js", "end": [ 1, 45 @@ -135,7 +129,6 @@ 1, 42 ], - "filepath": "class.js", "end": [ 1, 45 @@ -154,7 +147,6 @@ 1, 63 ], - "filepath": "class.js", "end": [ 1, 66 @@ -165,7 +157,6 @@ 1, 63 ], - "filepath": "class.js", "end": [ 1, 68 @@ -183,9 +174,9 @@ "filePaths": [ "class.js" ], - "sha1": "c787d2802f7dfeeff51937b38139a8938e04c56c", + "sha1": "9c20b127c193a62b80eda6b277bb7a909e7b761a", "gitDir": "test/corpus/repos/javascript", - "sha2": "f20c9ecfdf70a7813f639cd564573125531e0d36" + "sha2": "f89babcecc359be4cc277d1c9970a8deaa3e8fe6" } ,{ "testCaseDescription": "javascript-class-replacement-test", @@ -200,7 +191,6 @@ 1, 20 ], - "filepath": "class.js", "end": [ 1, 23 @@ -211,7 +201,6 @@ 1, 20 ], - "filepath": "class.js", "end": [ 1, 23 @@ -230,7 +219,6 @@ 1, 42 ], - "filepath": "class.js", "end": [ 1, 45 @@ -241,7 +229,6 @@ 1, 42 ], - "filepath": "class.js", "end": [ 1, 45 @@ -260,7 +247,6 @@ 1, 63 ], - "filepath": "class.js", "end": [ 1, 68 @@ -271,7 +257,6 @@ 1, 63 ], - "filepath": "class.js", "end": [ 1, 66 @@ -289,9 +274,9 @@ "filePaths": [ "class.js" ], - "sha1": "f20c9ecfdf70a7813f639cd564573125531e0d36", + "sha1": "f89babcecc359be4cc277d1c9970a8deaa3e8fe6", "gitDir": "test/corpus/repos/javascript", - "sha2": "8e2cbe60158dba7189d0557733ba469e25821a5a" + "sha2": "db12f186575ae386af489e213608fa3a80773747" } ,{ "testCaseDescription": "javascript-class-delete-replacement-test", @@ -305,7 +290,6 @@ 1, 1 ], - "filepath": "class.js", "end": [ 1, 85 @@ -322,7 +306,6 @@ 2, 1 ], - "filepath": "class.js", "end": [ 2, 87 @@ -339,7 +322,6 @@ 2, 1 ], - "filepath": "class.js", "end": [ 2, 85 @@ -356,9 +338,9 @@ "filePaths": [ "class.js" ], - "sha1": "8e2cbe60158dba7189d0557733ba469e25821a5a", + "sha1": "db12f186575ae386af489e213608fa3a80773747", "gitDir": "test/corpus/repos/javascript", - "sha2": "3a4bb98497d1b180a89c60a21d793144eec3a80a" + "sha2": "feb3a4cf1baa84520130badfe96c139a0d6dc94d" } ,{ "testCaseDescription": "javascript-class-delete-test", @@ -372,7 +354,6 @@ 1, 1 ], - "filepath": "class.js", "end": [ 1, 87 @@ -389,9 +370,9 @@ "filePaths": [ "class.js" ], - "sha1": "3a4bb98497d1b180a89c60a21d793144eec3a80a", + "sha1": "feb3a4cf1baa84520130badfe96c139a0d6dc94d", "gitDir": "test/corpus/repos/javascript", - "sha2": "73a6659aefa301b17817e63166f813cf0da70197" + "sha2": "a41d47574ddcd9f4427ab581e5651ed26ffc1b9d" } ,{ "testCaseDescription": "javascript-class-delete-rest-test", @@ -405,7 +386,6 @@ 1, 1 ], - "filepath": "class.js", "end": [ 1, 85 @@ -422,7 +402,7 @@ "filePaths": [ "class.js" ], - "sha1": "73a6659aefa301b17817e63166f813cf0da70197", + "sha1": "a41d47574ddcd9f4427ab581e5651ed26ffc1b9d", "gitDir": "test/corpus/repos/javascript", - "sha2": "b5b3abeccc0703872ec7867eef96c235e5b8c3e6" + "sha2": "395c6eece5c8b6aa98613ca7569ddd88f70d7988" }] diff --git a/test/corpus/diff-summaries/javascript/comma-operator.json b/test/corpus/diff-summaries/javascript/comma-operator.json index a2d3807ce..742fde82d 100644 --- a/test/corpus/diff-summaries/javascript/comma-operator.json +++ b/test/corpus/diff-summaries/javascript/comma-operator.json @@ -10,7 +10,6 @@ 1, 1 ], - "filepath": "comma-operator.js", "end": [ 1, 6 @@ -27,7 +26,6 @@ 1, 8 ], - "filepath": "comma-operator.js", "end": [ 1, 13 @@ -44,9 +42,9 @@ "filePaths": [ "comma-operator.js" ], - "sha1": "70e4311d385e03edb55b7d538def13b2388666a4", + "sha1": "c376ba3379a36f234ec18e27404102b3ec9c0794", "gitDir": "test/corpus/repos/javascript", - "sha2": "94d29d1950adb083431cd504a11d076f8edc1b50" + "sha2": "31e90b6b1c5c3dc917da063eaf26d247b75b5c46" } ,{ "testCaseDescription": "javascript-comma-operator-replacement-insert-test", @@ -60,7 +58,6 @@ 1, 1 ], - "filepath": "comma-operator.js", "end": [ 1, 23 @@ -77,7 +74,6 @@ 2, 1 ], - "filepath": "comma-operator.js", "end": [ 2, 6 @@ -94,7 +90,6 @@ 2, 8 ], - "filepath": "comma-operator.js", "end": [ 2, 13 @@ -111,9 +106,9 @@ "filePaths": [ "comma-operator.js" ], - "sha1": "94d29d1950adb083431cd504a11d076f8edc1b50", + "sha1": "31e90b6b1c5c3dc917da063eaf26d247b75b5c46", "gitDir": "test/corpus/repos/javascript", - "sha2": "221d6e5e7d9a4529a2c79e6f3768357d2427c456" + "sha2": "80531ffeb669b96cf79ad6c9ad2324d4c238e2a4" } ,{ "testCaseDescription": "javascript-comma-operator-delete-insert-test", @@ -127,7 +122,6 @@ 1, 1 ], - "filepath": "comma-operator.js", "end": [ 1, 6 @@ -144,7 +138,6 @@ 1, 8 ], - "filepath": "comma-operator.js", "end": [ 1, 13 @@ -161,7 +154,6 @@ 1, 1 ], - "filepath": "comma-operator.js", "end": [ 1, 23 @@ -178,9 +170,9 @@ "filePaths": [ "comma-operator.js" ], - "sha1": "221d6e5e7d9a4529a2c79e6f3768357d2427c456", + "sha1": "80531ffeb669b96cf79ad6c9ad2324d4c238e2a4", "gitDir": "test/corpus/repos/javascript", - "sha2": "1a2d810f3a951ea82bb8dc99556337cc1667070d" + "sha2": "8a61a54a5e569eb053d0bbdf9f2aa8093b66ffdc" } ,{ "testCaseDescription": "javascript-comma-operator-replacement-test", @@ -194,7 +186,6 @@ 1, 1 ], - "filepath": "comma-operator.js", "end": [ 1, 23 @@ -211,7 +202,6 @@ 1, 1 ], - "filepath": "comma-operator.js", "end": [ 1, 6 @@ -228,7 +218,6 @@ 1, 8 ], - "filepath": "comma-operator.js", "end": [ 1, 13 @@ -245,9 +234,9 @@ "filePaths": [ "comma-operator.js" ], - "sha1": "1a2d810f3a951ea82bb8dc99556337cc1667070d", + "sha1": "8a61a54a5e569eb053d0bbdf9f2aa8093b66ffdc", "gitDir": "test/corpus/repos/javascript", - "sha2": "2d35ba812a5ddc6f869f464cfb584121811af942" + "sha2": "4de76b87e19fa641bbde82250f5c1448582adde0" } ,{ "testCaseDescription": "javascript-comma-operator-delete-replacement-test", @@ -261,7 +250,6 @@ 1, 1 ], - "filepath": "comma-operator.js", "end": [ 1, 23 @@ -278,7 +266,6 @@ 2, 1 ], - "filepath": "comma-operator.js", "end": [ 2, 6 @@ -295,7 +282,6 @@ 2, 8 ], - "filepath": "comma-operator.js", "end": [ 2, 13 @@ -312,7 +298,6 @@ 2, 1 ], - "filepath": "comma-operator.js", "end": [ 2, 23 @@ -329,9 +314,9 @@ "filePaths": [ "comma-operator.js" ], - "sha1": "2d35ba812a5ddc6f869f464cfb584121811af942", + "sha1": "4de76b87e19fa641bbde82250f5c1448582adde0", "gitDir": "test/corpus/repos/javascript", - "sha2": "f383fad905cc774683ea1eda377a2274a2541497" + "sha2": "358a64dfe4454828ab1cd7632ea33aabf8791031" } ,{ "testCaseDescription": "javascript-comma-operator-delete-test", @@ -345,7 +330,6 @@ 1, 1 ], - "filepath": "comma-operator.js", "end": [ 1, 6 @@ -362,7 +346,6 @@ 1, 8 ], - "filepath": "comma-operator.js", "end": [ 1, 13 @@ -379,9 +362,9 @@ "filePaths": [ "comma-operator.js" ], - "sha1": "f383fad905cc774683ea1eda377a2274a2541497", + "sha1": "358a64dfe4454828ab1cd7632ea33aabf8791031", "gitDir": "test/corpus/repos/javascript", - "sha2": "4bc13b0b89c640f5006db4b024163b69ccc7c58e" + "sha2": "c7bc8d4656be920af42145c1ff818668ad25bcaa" } ,{ "testCaseDescription": "javascript-comma-operator-delete-rest-test", @@ -395,7 +378,6 @@ 1, 1 ], - "filepath": "comma-operator.js", "end": [ 1, 23 @@ -412,7 +394,7 @@ "filePaths": [ "comma-operator.js" ], - "sha1": "4bc13b0b89c640f5006db4b024163b69ccc7c58e", + "sha1": "c7bc8d4656be920af42145c1ff818668ad25bcaa", "gitDir": "test/corpus/repos/javascript", - "sha2": "dd182ba0e84ee13e2e979b15165cf1fe015755e7" + "sha2": "2a1ddb9a8c6d84924131fb18113f31eeade50718" }] diff --git a/test/corpus/diff-summaries/javascript/comment.json b/test/corpus/diff-summaries/javascript/comment.json index 4703d5f82..c17239fac 100644 --- a/test/corpus/diff-summaries/javascript/comment.json +++ b/test/corpus/diff-summaries/javascript/comment.json @@ -10,7 +10,6 @@ 1, 1 ], - "filepath": "comment.js", "end": [ 1, 22 @@ -27,9 +26,9 @@ "filePaths": [ "comment.js" ], - "sha1": "d3f20de8481cbd432e9c90f5583e6e599473d75e", + "sha1": "9ed8066a32b8ac3bc857ec9ffb963f12322f5224", "gitDir": "test/corpus/repos/javascript", - "sha2": "dce32df186cf64de3d31a1079ab51c803ff5f61d" + "sha2": "cbdd13e093a8640ad08ec76174b68cf07600c1ea" } ,{ "testCaseDescription": "javascript-comment-replacement-insert-test", @@ -43,7 +42,6 @@ 1, 1 ], - "filepath": "comment.js", "end": [ 3, 3 @@ -60,7 +58,6 @@ 4, 1 ], - "filepath": "comment.js", "end": [ 4, 22 @@ -77,9 +74,9 @@ "filePaths": [ "comment.js" ], - "sha1": "dce32df186cf64de3d31a1079ab51c803ff5f61d", + "sha1": "cbdd13e093a8640ad08ec76174b68cf07600c1ea", "gitDir": "test/corpus/repos/javascript", - "sha2": "f7fed3980e9c1bf33777cd64b90fd76509553063" + "sha2": "f5a91dac7a4f5f86c7a7cf2c69c5e988fb408712" } ,{ "testCaseDescription": "javascript-comment-delete-insert-test", @@ -94,7 +91,6 @@ 1, 1 ], - "filepath": "comment.js", "end": [ 3, 3 @@ -105,7 +101,6 @@ 1, 1 ], - "filepath": "comment.js", "end": [ 1, 22 @@ -123,9 +118,9 @@ "filePaths": [ "comment.js" ], - "sha1": "f7fed3980e9c1bf33777cd64b90fd76509553063", + "sha1": "f5a91dac7a4f5f86c7a7cf2c69c5e988fb408712", "gitDir": "test/corpus/repos/javascript", - "sha2": "0d2741ed46b3f3b132e1bd58de68531d8d73f93e" + "sha2": "c8bd2718371b28040fa981ce35a138725b120aad" } ,{ "testCaseDescription": "javascript-comment-replacement-test", @@ -140,7 +135,6 @@ 1, 1 ], - "filepath": "comment.js", "end": [ 1, 22 @@ -151,7 +145,6 @@ 1, 1 ], - "filepath": "comment.js", "end": [ 3, 3 @@ -169,9 +162,9 @@ "filePaths": [ "comment.js" ], - "sha1": "0d2741ed46b3f3b132e1bd58de68531d8d73f93e", + "sha1": "c8bd2718371b28040fa981ce35a138725b120aad", "gitDir": "test/corpus/repos/javascript", - "sha2": "05023387b5cd31e769396c4154612d370acba428" + "sha2": "f638e783e9d0ee750f8f201471d4b1b9e9f3f9a3" } ,{ "testCaseDescription": "javascript-comment-delete-replacement-test", @@ -185,7 +178,6 @@ 1, 1 ], - "filepath": "comment.js", "end": [ 3, 3 @@ -202,7 +194,6 @@ 4, 1 ], - "filepath": "comment.js", "end": [ 4, 22 @@ -219,7 +210,6 @@ 2, 1 ], - "filepath": "comment.js", "end": [ 4, 3 @@ -236,9 +226,9 @@ "filePaths": [ "comment.js" ], - "sha1": "05023387b5cd31e769396c4154612d370acba428", + "sha1": "f638e783e9d0ee750f8f201471d4b1b9e9f3f9a3", "gitDir": "test/corpus/repos/javascript", - "sha2": "80429e7adabaa54968b85e33b41fbdeeab99c61a" + "sha2": "48711051e73107b9a44cf4c146dbdbdcafea224f" } ,{ "testCaseDescription": "javascript-comment-delete-test", @@ -252,7 +242,6 @@ 1, 1 ], - "filepath": "comment.js", "end": [ 1, 22 @@ -269,9 +258,9 @@ "filePaths": [ "comment.js" ], - "sha1": "80429e7adabaa54968b85e33b41fbdeeab99c61a", + "sha1": "48711051e73107b9a44cf4c146dbdbdcafea224f", "gitDir": "test/corpus/repos/javascript", - "sha2": "98e0baa0daaf07a71c0dde4d4ba655943e235984" + "sha2": "8446a2ada4c302787a76d6f8654f66e0f14e9fa6" } ,{ "testCaseDescription": "javascript-comment-delete-rest-test", @@ -285,7 +274,6 @@ 1, 1 ], - "filepath": "comment.js", "end": [ 3, 3 @@ -302,7 +290,7 @@ "filePaths": [ "comment.js" ], - "sha1": "98e0baa0daaf07a71c0dde4d4ba655943e235984", + "sha1": "8446a2ada4c302787a76d6f8654f66e0f14e9fa6", "gitDir": "test/corpus/repos/javascript", - "sha2": "bfb8c510e7246eadb01815b4ede83df2539e0444" + "sha2": "af31bc75c5b7a9054f10c295c885d0cc2c5d1d06" }] diff --git a/test/corpus/diff-summaries/javascript/constructor-call.json b/test/corpus/diff-summaries/javascript/constructor-call.json index 7b6428609..52a26271f 100644 --- a/test/corpus/diff-summaries/javascript/constructor-call.json +++ b/test/corpus/diff-summaries/javascript/constructor-call.json @@ -10,7 +10,6 @@ 1, 1 ], - "filepath": "constructor-call.js", "end": [ 1, 27 @@ -27,9 +26,9 @@ "filePaths": [ "constructor-call.js" ], - "sha1": "e77e93003c7650329a3f14274c85d9ce07ba9273", + "sha1": "37b9064285baa63e16cc6b1c4b5128fed52fa082", "gitDir": "test/corpus/repos/javascript", - "sha2": "e282305b5c7dbd64df634b662d6e69e151904e41" + "sha2": "b8f33f052773b435e5d29e89aeaf9cf8b3a9e8a6" } ,{ "testCaseDescription": "javascript-constructor-call-replacement-insert-test", @@ -43,7 +42,6 @@ 1, 1 ], - "filepath": "constructor-call.js", "end": [ 1, 29 @@ -60,7 +58,6 @@ 2, 1 ], - "filepath": "constructor-call.js", "end": [ 2, 27 @@ -77,9 +74,9 @@ "filePaths": [ "constructor-call.js" ], - "sha1": "e282305b5c7dbd64df634b662d6e69e151904e41", + "sha1": "b8f33f052773b435e5d29e89aeaf9cf8b3a9e8a6", "gitDir": "test/corpus/repos/javascript", - "sha2": "206d378ae7bafc88a7cf46b917757761914ce46c" + "sha2": "fa501924dbaed310d84435b0c33ef97a068653e4" } ,{ "testCaseDescription": "javascript-constructor-call-delete-insert-test", @@ -94,7 +91,6 @@ 1, 21 ], - "filepath": "constructor-call.js", "end": [ 1, 28 @@ -105,7 +101,6 @@ 1, 21 ], - "filepath": "constructor-call.js", "end": [ 1, 26 @@ -123,9 +118,9 @@ "filePaths": [ "constructor-call.js" ], - "sha1": "206d378ae7bafc88a7cf46b917757761914ce46c", + "sha1": "fa501924dbaed310d84435b0c33ef97a068653e4", "gitDir": "test/corpus/repos/javascript", - "sha2": "2a7d4a7d282cb4595bbf27ff91b5efeae2076479" + "sha2": "9c7fb90945f08ad72efbcd243221cef5ce8d9732" } ,{ "testCaseDescription": "javascript-constructor-call-replacement-test", @@ -140,7 +135,6 @@ 1, 21 ], - "filepath": "constructor-call.js", "end": [ 1, 26 @@ -151,7 +145,6 @@ 1, 21 ], - "filepath": "constructor-call.js", "end": [ 1, 28 @@ -169,9 +162,9 @@ "filePaths": [ "constructor-call.js" ], - "sha1": "2a7d4a7d282cb4595bbf27ff91b5efeae2076479", + "sha1": "9c7fb90945f08ad72efbcd243221cef5ce8d9732", "gitDir": "test/corpus/repos/javascript", - "sha2": "b389ea9f4bb4258e145bcd9e5ee65339bdb5ca81" + "sha2": "bb66b026044f3944a08fec17c572b7b8867decda" } ,{ "testCaseDescription": "javascript-constructor-call-delete-replacement-test", @@ -185,7 +178,6 @@ 1, 1 ], - "filepath": "constructor-call.js", "end": [ 1, 29 @@ -202,7 +194,6 @@ 2, 1 ], - "filepath": "constructor-call.js", "end": [ 2, 27 @@ -219,7 +210,6 @@ 2, 1 ], - "filepath": "constructor-call.js", "end": [ 2, 29 @@ -236,9 +226,9 @@ "filePaths": [ "constructor-call.js" ], - "sha1": "b389ea9f4bb4258e145bcd9e5ee65339bdb5ca81", + "sha1": "bb66b026044f3944a08fec17c572b7b8867decda", "gitDir": "test/corpus/repos/javascript", - "sha2": "11fe2e13ee306e5fa1bcf3257f0e29f2d4ed5335" + "sha2": "3669aebc1d501fba80efddd2a0b53b669b045ffa" } ,{ "testCaseDescription": "javascript-constructor-call-delete-test", @@ -252,7 +242,6 @@ 1, 1 ], - "filepath": "constructor-call.js", "end": [ 1, 27 @@ -269,9 +258,9 @@ "filePaths": [ "constructor-call.js" ], - "sha1": "11fe2e13ee306e5fa1bcf3257f0e29f2d4ed5335", + "sha1": "3669aebc1d501fba80efddd2a0b53b669b045ffa", "gitDir": "test/corpus/repos/javascript", - "sha2": "fb8da2e7dd3c3248beb53c9b9a33ab28c9966d78" + "sha2": "aada0c4456c077928d7b286809c61323c9315147" } ,{ "testCaseDescription": "javascript-constructor-call-delete-rest-test", @@ -285,7 +274,6 @@ 1, 1 ], - "filepath": "constructor-call.js", "end": [ 1, 29 @@ -302,7 +290,7 @@ "filePaths": [ "constructor-call.js" ], - "sha1": "fb8da2e7dd3c3248beb53c9b9a33ab28c9966d78", + "sha1": "aada0c4456c077928d7b286809c61323c9315147", "gitDir": "test/corpus/repos/javascript", - "sha2": "2583ff8eb54838a4bae616ec1c051ebfc0c6b21c" + "sha2": "770dfcd929f8deaec3cf8028327930c422ee1814" }] diff --git a/test/corpus/diff-summaries/javascript/delete-operator.json b/test/corpus/diff-summaries/javascript/delete-operator.json index be68cdd49..7a7a9578b 100644 --- a/test/corpus/diff-summaries/javascript/delete-operator.json +++ b/test/corpus/diff-summaries/javascript/delete-operator.json @@ -10,7 +10,6 @@ 1, 1 ], - "filepath": "delete-operator.js", "end": [ 1, 21 @@ -27,9 +26,9 @@ "filePaths": [ "delete-operator.js" ], - "sha1": "d7d8b169c8385f3a91f99dd299e5ebb566e5a346", + "sha1": "34d611dc6839b42bba50f800508e3c1eed940690", "gitDir": "test/corpus/repos/javascript", - "sha2": "6c6e619841b05739ffd85569a1328aabe62f84a6" + "sha2": "9c01dfb007ff3853c71c2ed944ccf83ae4a4899e" } ,{ "testCaseDescription": "javascript-delete-operator-replacement-insert-test", @@ -43,7 +42,6 @@ 1, 1 ], - "filepath": "delete-operator.js", "end": [ 1, 18 @@ -60,7 +58,6 @@ 2, 1 ], - "filepath": "delete-operator.js", "end": [ 2, 21 @@ -77,9 +74,9 @@ "filePaths": [ "delete-operator.js" ], - "sha1": "6c6e619841b05739ffd85569a1328aabe62f84a6", + "sha1": "9c01dfb007ff3853c71c2ed944ccf83ae4a4899e", "gitDir": "test/corpus/repos/javascript", - "sha2": "b0ff0d9a3df842084c04a09dea21d8d18c70a35a" + "sha2": "fcd04c63372795e232f0ab1dc003078a11e23348" } ,{ "testCaseDescription": "javascript-delete-operator-delete-insert-test", @@ -94,7 +91,6 @@ 1, 1 ], - "filepath": "delete-operator.js", "end": [ 1, 18 @@ -105,7 +101,6 @@ 1, 1 ], - "filepath": "delete-operator.js", "end": [ 1, 21 @@ -123,9 +118,9 @@ "filePaths": [ "delete-operator.js" ], - "sha1": "b0ff0d9a3df842084c04a09dea21d8d18c70a35a", + "sha1": "fcd04c63372795e232f0ab1dc003078a11e23348", "gitDir": "test/corpus/repos/javascript", - "sha2": "da51d558c50a3b77f771324583cc0d7550a8e515" + "sha2": "54acda735d0aa3817a65ab8bae18ac9c3249299f" } ,{ "testCaseDescription": "javascript-delete-operator-replacement-test", @@ -140,7 +135,6 @@ 1, 1 ], - "filepath": "delete-operator.js", "end": [ 1, 21 @@ -151,7 +145,6 @@ 1, 1 ], - "filepath": "delete-operator.js", "end": [ 1, 18 @@ -169,9 +162,9 @@ "filePaths": [ "delete-operator.js" ], - "sha1": "da51d558c50a3b77f771324583cc0d7550a8e515", + "sha1": "54acda735d0aa3817a65ab8bae18ac9c3249299f", "gitDir": "test/corpus/repos/javascript", - "sha2": "061a6799cac8f6e7d6daff84708dd2b9d2f1a124" + "sha2": "16e956f11b3ecc44abf81b4c33cddbd36c9222a7" } ,{ "testCaseDescription": "javascript-delete-operator-delete-replacement-test", @@ -185,7 +178,6 @@ 1, 1 ], - "filepath": "delete-operator.js", "end": [ 1, 18 @@ -202,7 +194,6 @@ 2, 1 ], - "filepath": "delete-operator.js", "end": [ 2, 21 @@ -219,7 +210,6 @@ 2, 1 ], - "filepath": "delete-operator.js", "end": [ 2, 18 @@ -236,9 +226,9 @@ "filePaths": [ "delete-operator.js" ], - "sha1": "061a6799cac8f6e7d6daff84708dd2b9d2f1a124", + "sha1": "16e956f11b3ecc44abf81b4c33cddbd36c9222a7", "gitDir": "test/corpus/repos/javascript", - "sha2": "b5fd60da6d762332b03e0d20e55f81cf4436ee5f" + "sha2": "91fc755fdc45f6c82da10cdb9078ff2d8ec66c9c" } ,{ "testCaseDescription": "javascript-delete-operator-delete-test", @@ -252,7 +242,6 @@ 1, 1 ], - "filepath": "delete-operator.js", "end": [ 1, 21 @@ -269,9 +258,9 @@ "filePaths": [ "delete-operator.js" ], - "sha1": "b5fd60da6d762332b03e0d20e55f81cf4436ee5f", + "sha1": "91fc755fdc45f6c82da10cdb9078ff2d8ec66c9c", "gitDir": "test/corpus/repos/javascript", - "sha2": "7fac635a01cb2cde4cf5830e93551808729258c8" + "sha2": "dadef7d3a1d78afcdb53140c1c32f0bd93f75580" } ,{ "testCaseDescription": "javascript-delete-operator-delete-rest-test", @@ -285,7 +274,6 @@ 1, 1 ], - "filepath": "delete-operator.js", "end": [ 1, 18 @@ -302,7 +290,7 @@ "filePaths": [ "delete-operator.js" ], - "sha1": "7fac635a01cb2cde4cf5830e93551808729258c8", + "sha1": "dadef7d3a1d78afcdb53140c1c32f0bd93f75580", "gitDir": "test/corpus/repos/javascript", - "sha2": "f6b6a39365ea495fba9ad72496f299b47250db15" + "sha2": "d14d7b09c6761ab1a14c5aeda0a105d44c520617" }] diff --git a/test/corpus/diff-summaries/javascript/do-while-statement.json b/test/corpus/diff-summaries/javascript/do-while-statement.json index c79bd4b5b..3eedde9ba 100644 --- a/test/corpus/diff-summaries/javascript/do-while-statement.json +++ b/test/corpus/diff-summaries/javascript/do-while-statement.json @@ -10,7 +10,6 @@ 1, 1 ], - "filepath": "do-while-statement.js", "end": [ 1, 42 @@ -27,9 +26,9 @@ "filePaths": [ "do-while-statement.js" ], - "sha1": "1dfeac8c9e51379d4ffcbc1b381c7a6b88ce13bf", + "sha1": "3dadf24ea6dd60cf63f2599d16951764a34aea81", "gitDir": "test/corpus/repos/javascript", - "sha2": "bd4c404c2241fa600f63d20dd599545f7c31b45f" + "sha2": "5ac1a1a4fe9eda5e5fd161253a6d91501f1b3ce1" } ,{ "testCaseDescription": "javascript-do-while-statement-replacement-insert-test", @@ -43,7 +42,6 @@ 1, 1 ], - "filepath": "do-while-statement.js", "end": [ 1, 48 @@ -60,7 +58,6 @@ 2, 1 ], - "filepath": "do-while-statement.js", "end": [ 2, 42 @@ -77,9 +74,9 @@ "filePaths": [ "do-while-statement.js" ], - "sha1": "bd4c404c2241fa600f63d20dd599545f7c31b45f", + "sha1": "5ac1a1a4fe9eda5e5fd161253a6d91501f1b3ce1", "gitDir": "test/corpus/repos/javascript", - "sha2": "d47acaaff3e391d7973dfed79c545312a92b1201" + "sha2": "ba86b912e5954ec48b6e49bca4c6bf3f24debf71" } ,{ "testCaseDescription": "javascript-do-while-statement-delete-insert-test", @@ -94,7 +91,6 @@ 1, 18 ], - "filepath": "do-while-statement.js", "end": [ 1, 29 @@ -105,7 +101,6 @@ 1, 18 ], - "filepath": "do-while-statement.js", "end": [ 1, 24 @@ -124,7 +119,6 @@ 1, 41 ], - "filepath": "do-while-statement.js", "end": [ 1, 46 @@ -135,7 +129,6 @@ 1, 36 ], - "filepath": "do-while-statement.js", "end": [ 1, 40 @@ -153,9 +146,9 @@ "filePaths": [ "do-while-statement.js" ], - "sha1": "d47acaaff3e391d7973dfed79c545312a92b1201", + "sha1": "ba86b912e5954ec48b6e49bca4c6bf3f24debf71", "gitDir": "test/corpus/repos/javascript", - "sha2": "1472e9658b3468f31af838a42dbc4fca21e588d7" + "sha2": "224a8c099bc7a1282813dd3f2d4ed7d8c87a3f0f" } ,{ "testCaseDescription": "javascript-do-while-statement-replacement-test", @@ -170,7 +163,6 @@ 1, 18 ], - "filepath": "do-while-statement.js", "end": [ 1, 24 @@ -181,7 +173,6 @@ 1, 18 ], - "filepath": "do-while-statement.js", "end": [ 1, 29 @@ -200,7 +191,6 @@ 1, 36 ], - "filepath": "do-while-statement.js", "end": [ 1, 40 @@ -211,7 +201,6 @@ 1, 41 ], - "filepath": "do-while-statement.js", "end": [ 1, 46 @@ -229,9 +218,9 @@ "filePaths": [ "do-while-statement.js" ], - "sha1": "1472e9658b3468f31af838a42dbc4fca21e588d7", + "sha1": "224a8c099bc7a1282813dd3f2d4ed7d8c87a3f0f", "gitDir": "test/corpus/repos/javascript", - "sha2": "7a91cddb5ade8ebac85bd9a9e45a22b1f8e17f0e" + "sha2": "1363c42479d68b43b946500050acea6a3ec19511" } ,{ "testCaseDescription": "javascript-do-while-statement-delete-replacement-test", @@ -245,7 +234,6 @@ 1, 1 ], - "filepath": "do-while-statement.js", "end": [ 1, 48 @@ -262,7 +250,6 @@ 2, 1 ], - "filepath": "do-while-statement.js", "end": [ 2, 42 @@ -279,7 +266,6 @@ 2, 1 ], - "filepath": "do-while-statement.js", "end": [ 2, 48 @@ -296,9 +282,9 @@ "filePaths": [ "do-while-statement.js" ], - "sha1": "7a91cddb5ade8ebac85bd9a9e45a22b1f8e17f0e", + "sha1": "1363c42479d68b43b946500050acea6a3ec19511", "gitDir": "test/corpus/repos/javascript", - "sha2": "57869194a0812835d5ac9ebb903d3b15f6da4265" + "sha2": "feb5169e88f28961b09f7527b8af6819931f39f3" } ,{ "testCaseDescription": "javascript-do-while-statement-delete-test", @@ -312,7 +298,6 @@ 1, 1 ], - "filepath": "do-while-statement.js", "end": [ 1, 42 @@ -329,9 +314,9 @@ "filePaths": [ "do-while-statement.js" ], - "sha1": "57869194a0812835d5ac9ebb903d3b15f6da4265", + "sha1": "feb5169e88f28961b09f7527b8af6819931f39f3", "gitDir": "test/corpus/repos/javascript", - "sha2": "6432a7bc0783629c3afe32c6b61b577d1bb77aea" + "sha2": "e6b31e8c000b83aef153563e940ba6753a81aa13" } ,{ "testCaseDescription": "javascript-do-while-statement-delete-rest-test", @@ -345,7 +330,6 @@ 1, 1 ], - "filepath": "do-while-statement.js", "end": [ 1, 48 @@ -362,7 +346,7 @@ "filePaths": [ "do-while-statement.js" ], - "sha1": "6432a7bc0783629c3afe32c6b61b577d1bb77aea", + "sha1": "e6b31e8c000b83aef153563e940ba6753a81aa13", "gitDir": "test/corpus/repos/javascript", - "sha2": "4b2b35f5d9900e04b167abcf83c279790a555fa4" + "sha2": "a61175fe3edb3376731a61e36fbe795857288cb2" }] diff --git a/test/corpus/diff-summaries/javascript/false.json b/test/corpus/diff-summaries/javascript/false.json index ee34d82b5..0df5d715e 100644 --- a/test/corpus/diff-summaries/javascript/false.json +++ b/test/corpus/diff-summaries/javascript/false.json @@ -10,7 +10,6 @@ 1, 1 ], - "filepath": "false.js", "end": [ 1, 6 @@ -27,9 +26,9 @@ "filePaths": [ "false.js" ], - "sha1": "4bdbc3b261a181ab8a66d17f1946997d7cf9e70c", + "sha1": "bc59c08d8b5b00715bbf8e852bee86bfed8d5f03", "gitDir": "test/corpus/repos/javascript", - "sha2": "291d22d3328572cc0ba03c8fe6f2cd251829f4ad" + "sha2": "0e8162ddf892bf944707eefa68da4d8c3097ee5e" } ,{ "testCaseDescription": "javascript-false-replacement-insert-test", @@ -43,7 +42,6 @@ 1, 1 ], - "filepath": "false.js", "end": [ 1, 14 @@ -60,7 +58,6 @@ 2, 1 ], - "filepath": "false.js", "end": [ 2, 6 @@ -77,9 +74,9 @@ "filePaths": [ "false.js" ], - "sha1": "291d22d3328572cc0ba03c8fe6f2cd251829f4ad", + "sha1": "0e8162ddf892bf944707eefa68da4d8c3097ee5e", "gitDir": "test/corpus/repos/javascript", - "sha2": "b2e1de5041bb2f680f34ecbc6e03a85995718a84" + "sha2": "827e84992521a53a4672e7487814a3d904570c3c" } ,{ "testCaseDescription": "javascript-false-delete-insert-test", @@ -93,7 +90,6 @@ 1, 1 ], - "filepath": "false.js", "end": [ 1, 6 @@ -110,7 +106,6 @@ 1, 1 ], - "filepath": "false.js", "end": [ 1, 14 @@ -127,9 +122,9 @@ "filePaths": [ "false.js" ], - "sha1": "b2e1de5041bb2f680f34ecbc6e03a85995718a84", + "sha1": "827e84992521a53a4672e7487814a3d904570c3c", "gitDir": "test/corpus/repos/javascript", - "sha2": "8cad66c7d19c61e0de7f8616a842ee3d2319bef5" + "sha2": "8ad16f2c510212119c87a32df1d0661c7f091533" } ,{ "testCaseDescription": "javascript-false-replacement-test", @@ -143,7 +138,6 @@ 1, 1 ], - "filepath": "false.js", "end": [ 1, 14 @@ -160,7 +154,6 @@ 1, 1 ], - "filepath": "false.js", "end": [ 1, 6 @@ -177,9 +170,9 @@ "filePaths": [ "false.js" ], - "sha1": "8cad66c7d19c61e0de7f8616a842ee3d2319bef5", + "sha1": "8ad16f2c510212119c87a32df1d0661c7f091533", "gitDir": "test/corpus/repos/javascript", - "sha2": "618390d2b227652f399804f8c1e01c26d7054d0a" + "sha2": "5665bce4ee27c2b5f56afbc88b0ca17f85902c6a" } ,{ "testCaseDescription": "javascript-false-delete-replacement-test", @@ -193,7 +186,6 @@ 1, 1 ], - "filepath": "false.js", "end": [ 1, 14 @@ -210,7 +202,6 @@ 2, 1 ], - "filepath": "false.js", "end": [ 2, 6 @@ -227,7 +218,6 @@ 2, 1 ], - "filepath": "false.js", "end": [ 2, 14 @@ -244,9 +234,9 @@ "filePaths": [ "false.js" ], - "sha1": "618390d2b227652f399804f8c1e01c26d7054d0a", + "sha1": "5665bce4ee27c2b5f56afbc88b0ca17f85902c6a", "gitDir": "test/corpus/repos/javascript", - "sha2": "9d0f2ba31db2545c092de8d363d26ecd09f8f5d1" + "sha2": "5e7609a2a963055a420461b6743e96adb7cf9b88" } ,{ "testCaseDescription": "javascript-false-delete-test", @@ -260,7 +250,6 @@ 1, 1 ], - "filepath": "false.js", "end": [ 1, 6 @@ -277,9 +266,9 @@ "filePaths": [ "false.js" ], - "sha1": "9d0f2ba31db2545c092de8d363d26ecd09f8f5d1", + "sha1": "5e7609a2a963055a420461b6743e96adb7cf9b88", "gitDir": "test/corpus/repos/javascript", - "sha2": "7ae3334729126248117acf5177540fbe52f5c4b3" + "sha2": "1a3f66f5555eef7dbe41dd82451d089a5c3648d6" } ,{ "testCaseDescription": "javascript-false-delete-rest-test", @@ -293,7 +282,6 @@ 1, 1 ], - "filepath": "false.js", "end": [ 1, 14 @@ -310,7 +298,7 @@ "filePaths": [ "false.js" ], - "sha1": "7ae3334729126248117acf5177540fbe52f5c4b3", + "sha1": "1a3f66f5555eef7dbe41dd82451d089a5c3648d6", "gitDir": "test/corpus/repos/javascript", - "sha2": "70901cee54467ad046311d039d1dca528a0a7111" + "sha2": "87ef7d96585dfee34d9371968cd3cbec7f8a1d97" }] diff --git a/test/corpus/diff-summaries/javascript/for-in-statement.json b/test/corpus/diff-summaries/javascript/for-in-statement.json index 4b308db51..fcec7698b 100644 --- a/test/corpus/diff-summaries/javascript/for-in-statement.json +++ b/test/corpus/diff-summaries/javascript/for-in-statement.json @@ -10,7 +10,6 @@ 1, 1 ], - "filepath": "for-in-statement.js", "end": [ 1, 35 @@ -27,9 +26,9 @@ "filePaths": [ "for-in-statement.js" ], - "sha1": "e9fcb09c83fad74eddeca9ca622366a53a55888b", + "sha1": "12a3949b01e7ecc688735f731b84ba631a80c1c1", "gitDir": "test/corpus/repos/javascript", - "sha2": "cb63b2c22210e3c6fc67c0cf62a76236aa023b2b" + "sha2": "568db4c6d69437c83ad4d9eece85fb2d40203527" } ,{ "testCaseDescription": "javascript-for-in-statement-replacement-insert-test", @@ -43,7 +42,6 @@ 1, 1 ], - "filepath": "for-in-statement.js", "end": [ 1, 32 @@ -60,7 +58,6 @@ 2, 1 ], - "filepath": "for-in-statement.js", "end": [ 2, 35 @@ -77,9 +74,9 @@ "filePaths": [ "for-in-statement.js" ], - "sha1": "cb63b2c22210e3c6fc67c0cf62a76236aa023b2b", + "sha1": "568db4c6d69437c83ad4d9eece85fb2d40203527", "gitDir": "test/corpus/repos/javascript", - "sha2": "fc7099de96759e8a9b1c25c1f362d985aa32aceb" + "sha2": "424256ee4d0b8003e66b38b569c8a5200616560e" } ,{ "testCaseDescription": "javascript-for-in-statement-delete-insert-test", @@ -94,7 +91,6 @@ 1, 6 ], - "filepath": "for-in-statement.js", "end": [ 1, 10 @@ -105,7 +101,6 @@ 1, 6 ], - "filepath": "for-in-statement.js", "end": [ 1, 11 @@ -124,7 +119,6 @@ 1, 14 ], - "filepath": "for-in-statement.js", "end": [ 1, 19 @@ -135,7 +129,6 @@ 1, 15 ], - "filepath": "for-in-statement.js", "end": [ 1, 21 @@ -154,7 +147,6 @@ 1, 23 ], - "filepath": "for-in-statement.js", "end": [ 1, 27 @@ -165,7 +157,6 @@ 1, 25 ], - "filepath": "for-in-statement.js", "end": [ 1, 30 @@ -183,9 +174,9 @@ "filePaths": [ "for-in-statement.js" ], - "sha1": "fc7099de96759e8a9b1c25c1f362d985aa32aceb", + "sha1": "424256ee4d0b8003e66b38b569c8a5200616560e", "gitDir": "test/corpus/repos/javascript", - "sha2": "7b1f62adaf598bdc63c501b5f6e9a38b7895442d" + "sha2": "e57446ddf477ccf71ad7f59e4a935f2fb09bdad9" } ,{ "testCaseDescription": "javascript-for-in-statement-replacement-test", @@ -200,7 +191,6 @@ 1, 6 ], - "filepath": "for-in-statement.js", "end": [ 1, 11 @@ -211,7 +201,6 @@ 1, 6 ], - "filepath": "for-in-statement.js", "end": [ 1, 10 @@ -230,7 +219,6 @@ 1, 15 ], - "filepath": "for-in-statement.js", "end": [ 1, 21 @@ -241,7 +229,6 @@ 1, 14 ], - "filepath": "for-in-statement.js", "end": [ 1, 19 @@ -260,7 +247,6 @@ 1, 25 ], - "filepath": "for-in-statement.js", "end": [ 1, 30 @@ -271,7 +257,6 @@ 1, 23 ], - "filepath": "for-in-statement.js", "end": [ 1, 27 @@ -289,9 +274,9 @@ "filePaths": [ "for-in-statement.js" ], - "sha1": "7b1f62adaf598bdc63c501b5f6e9a38b7895442d", + "sha1": "e57446ddf477ccf71ad7f59e4a935f2fb09bdad9", "gitDir": "test/corpus/repos/javascript", - "sha2": "c16de6d4fe5ec69f259db76c8e998d417da9e961" + "sha2": "e652cb33755d7d6c916910cdec530b0608efc157" } ,{ "testCaseDescription": "javascript-for-in-statement-delete-replacement-test", @@ -305,7 +290,6 @@ 1, 1 ], - "filepath": "for-in-statement.js", "end": [ 1, 32 @@ -322,7 +306,6 @@ 2, 1 ], - "filepath": "for-in-statement.js", "end": [ 2, 35 @@ -339,7 +322,6 @@ 2, 1 ], - "filepath": "for-in-statement.js", "end": [ 2, 32 @@ -356,9 +338,9 @@ "filePaths": [ "for-in-statement.js" ], - "sha1": "c16de6d4fe5ec69f259db76c8e998d417da9e961", + "sha1": "e652cb33755d7d6c916910cdec530b0608efc157", "gitDir": "test/corpus/repos/javascript", - "sha2": "f336fb995c12c39b8e3df68a0cb67022ea149f7d" + "sha2": "f7bdd90fd30fb31f8b8c9e2c2ccfd43f327cb9cf" } ,{ "testCaseDescription": "javascript-for-in-statement-delete-test", @@ -372,7 +354,6 @@ 1, 1 ], - "filepath": "for-in-statement.js", "end": [ 1, 35 @@ -389,9 +370,9 @@ "filePaths": [ "for-in-statement.js" ], - "sha1": "f336fb995c12c39b8e3df68a0cb67022ea149f7d", + "sha1": "f7bdd90fd30fb31f8b8c9e2c2ccfd43f327cb9cf", "gitDir": "test/corpus/repos/javascript", - "sha2": "9b37944073bb49efd933e0884ccd6b8c1071f803" + "sha2": "2f59732701f26c61644d9cfde92375851a7d6ec4" } ,{ "testCaseDescription": "javascript-for-in-statement-delete-rest-test", @@ -405,7 +386,6 @@ 1, 1 ], - "filepath": "for-in-statement.js", "end": [ 1, 32 @@ -422,7 +402,7 @@ "filePaths": [ "for-in-statement.js" ], - "sha1": "9b37944073bb49efd933e0884ccd6b8c1071f803", + "sha1": "2f59732701f26c61644d9cfde92375851a7d6ec4", "gitDir": "test/corpus/repos/javascript", - "sha2": "aa8be129d06030fa7cb344ba9e16f5ad9eff8e47" + "sha2": "92dce519bc0a25951a62cfcf3a1069969a20938c" }] diff --git a/test/corpus/diff-summaries/javascript/for-loop-with-in-statement.json b/test/corpus/diff-summaries/javascript/for-loop-with-in-statement.json index 5bddc453f..7d26d3efc 100644 --- a/test/corpus/diff-summaries/javascript/for-loop-with-in-statement.json +++ b/test/corpus/diff-summaries/javascript/for-loop-with-in-statement.json @@ -10,7 +10,6 @@ 1, 1 ], - "filepath": "for-loop-with-in-statement.js", "end": [ 1, 63 @@ -27,9 +26,9 @@ "filePaths": [ "for-loop-with-in-statement.js" ], - "sha1": "2ed03a05e45eb7ba8974047b60a101f32957a87e", + "sha1": "2762aadfb1df20b18044fd4529c8cd573d357cc9", "gitDir": "test/corpus/repos/javascript", - "sha2": "c6067cf288dac3007ad9da590443f7b7998e7939" + "sha2": "adad02fe14bb8fefc9437fed0725b7b49b837d04" } ,{ "testCaseDescription": "javascript-for-loop-with-in-statement-replacement-insert-test", @@ -43,7 +42,6 @@ 1, 1 ], - "filepath": "for-loop-with-in-statement.js", "end": [ 1, 73 @@ -60,7 +58,6 @@ 2, 1 ], - "filepath": "for-loop-with-in-statement.js", "end": [ 2, 63 @@ -77,9 +74,9 @@ "filePaths": [ "for-loop-with-in-statement.js" ], - "sha1": "c6067cf288dac3007ad9da590443f7b7998e7939", + "sha1": "adad02fe14bb8fefc9437fed0725b7b49b837d04", "gitDir": "test/corpus/repos/javascript", - "sha2": "f22b188ca726f6296db43fac4d9485e4546aa4f2" + "sha2": "1f3fc5b85a5281e578b3304181604b65217349e9" } ,{ "testCaseDescription": "javascript-for-loop-with-in-statement-delete-insert-test", @@ -94,7 +91,6 @@ 1, 6 ], - "filepath": "for-loop-with-in-statement.js", "end": [ 1, 14 @@ -105,7 +101,6 @@ 1, 6 ], - "filepath": "for-loop-with-in-statement.js", "end": [ 1, 9 @@ -124,7 +119,6 @@ 1, 52 ], - "filepath": "for-loop-with-in-statement.js", "end": [ 1, 68 @@ -135,7 +129,6 @@ 1, 47 ], - "filepath": "for-loop-with-in-statement.js", "end": [ 1, 58 @@ -153,9 +146,9 @@ "filePaths": [ "for-loop-with-in-statement.js" ], - "sha1": "f22b188ca726f6296db43fac4d9485e4546aa4f2", + "sha1": "1f3fc5b85a5281e578b3304181604b65217349e9", "gitDir": "test/corpus/repos/javascript", - "sha2": "7adbbe1dbae09e993deabf1b97732ee328c20ef8" + "sha2": "14938b92d64697c66364baabc4277e0cd925f9d9" } ,{ "testCaseDescription": "javascript-for-loop-with-in-statement-replacement-test", @@ -170,7 +163,6 @@ 1, 6 ], - "filepath": "for-loop-with-in-statement.js", "end": [ 1, 9 @@ -181,7 +173,6 @@ 1, 6 ], - "filepath": "for-loop-with-in-statement.js", "end": [ 1, 14 @@ -200,7 +191,6 @@ 1, 47 ], - "filepath": "for-loop-with-in-statement.js", "end": [ 1, 58 @@ -211,7 +201,6 @@ 1, 52 ], - "filepath": "for-loop-with-in-statement.js", "end": [ 1, 68 @@ -229,9 +218,9 @@ "filePaths": [ "for-loop-with-in-statement.js" ], - "sha1": "7adbbe1dbae09e993deabf1b97732ee328c20ef8", + "sha1": "14938b92d64697c66364baabc4277e0cd925f9d9", "gitDir": "test/corpus/repos/javascript", - "sha2": "1ec3655a27c67e6e57c8b5f7030ffd6cce087dca" + "sha2": "44b34c087ea7c44395cd8fc72818925eeb24b67e" } ,{ "testCaseDescription": "javascript-for-loop-with-in-statement-delete-replacement-test", @@ -245,7 +234,6 @@ 1, 1 ], - "filepath": "for-loop-with-in-statement.js", "end": [ 1, 73 @@ -262,7 +250,6 @@ 2, 1 ], - "filepath": "for-loop-with-in-statement.js", "end": [ 2, 63 @@ -279,7 +266,6 @@ 2, 1 ], - "filepath": "for-loop-with-in-statement.js", "end": [ 2, 73 @@ -296,9 +282,9 @@ "filePaths": [ "for-loop-with-in-statement.js" ], - "sha1": "1ec3655a27c67e6e57c8b5f7030ffd6cce087dca", + "sha1": "44b34c087ea7c44395cd8fc72818925eeb24b67e", "gitDir": "test/corpus/repos/javascript", - "sha2": "bd03884bffc71f2aa9b5adb5cb0b2740e4ce0039" + "sha2": "8db9fc5ca6b6b08b797cf0954a326b1d72e32657" } ,{ "testCaseDescription": "javascript-for-loop-with-in-statement-delete-test", @@ -312,7 +298,6 @@ 1, 1 ], - "filepath": "for-loop-with-in-statement.js", "end": [ 1, 63 @@ -329,9 +314,9 @@ "filePaths": [ "for-loop-with-in-statement.js" ], - "sha1": "bd03884bffc71f2aa9b5adb5cb0b2740e4ce0039", + "sha1": "8db9fc5ca6b6b08b797cf0954a326b1d72e32657", "gitDir": "test/corpus/repos/javascript", - "sha2": "8735e286179888b48af0039634525b3ac9d574bc" + "sha2": "4c3269d570707ef8b45c8660494d318fa4e49614" } ,{ "testCaseDescription": "javascript-for-loop-with-in-statement-delete-rest-test", @@ -345,7 +330,6 @@ 1, 1 ], - "filepath": "for-loop-with-in-statement.js", "end": [ 1, 73 @@ -362,7 +346,7 @@ "filePaths": [ "for-loop-with-in-statement.js" ], - "sha1": "8735e286179888b48af0039634525b3ac9d574bc", + "sha1": "4c3269d570707ef8b45c8660494d318fa4e49614", "gitDir": "test/corpus/repos/javascript", - "sha2": "e7588cafe7a823a1dce9ddba49bcb503476dc672" + "sha2": "ca4c516f2d2c350b12fd36007d5c8ec2f5d6fe42" }] diff --git a/test/corpus/diff-summaries/javascript/for-of-statement.json b/test/corpus/diff-summaries/javascript/for-of-statement.json index 24ac005d9..b4bf1a2cb 100644 --- a/test/corpus/diff-summaries/javascript/for-of-statement.json +++ b/test/corpus/diff-summaries/javascript/for-of-statement.json @@ -10,7 +10,6 @@ 1, 1 ], - "filepath": "for-of-statement.js", "end": [ 1, 43 @@ -27,9 +26,9 @@ "filePaths": [ "for-of-statement.js" ], - "sha1": "e7588cafe7a823a1dce9ddba49bcb503476dc672", + "sha1": "5079af56f5049cde622a571fb286589b471549e5", "gitDir": "test/corpus/repos/javascript", - "sha2": "c37d0cae68a2013dfd17781ac2ff2d8b669ab9d7" + "sha2": "7897caa7d3f395e6fc8421235775076903bfeea3" } ,{ "testCaseDescription": "javascript-for-of-statement-replacement-insert-test", @@ -43,7 +42,6 @@ 1, 1 ], - "filepath": "for-of-statement.js", "end": [ 1, 46 @@ -60,7 +58,6 @@ 2, 1 ], - "filepath": "for-of-statement.js", "end": [ 2, 43 @@ -77,9 +74,9 @@ "filePaths": [ "for-of-statement.js" ], - "sha1": "c37d0cae68a2013dfd17781ac2ff2d8b669ab9d7", + "sha1": "7897caa7d3f395e6fc8421235775076903bfeea3", "gitDir": "test/corpus/repos/javascript", - "sha2": "cf9ed207fbbfb8cb068aedf35c5a7d1c95440d06" + "sha2": "764b4aec6e49bf027190ab1e5083bdd35a055279" } ,{ "testCaseDescription": "javascript-for-of-statement-delete-insert-test", @@ -94,7 +91,6 @@ 1, 10 ], - "filepath": "for-of-statement.js", "end": [ 1, 15 @@ -105,7 +101,6 @@ 1, 10 ], - "filepath": "for-of-statement.js", "end": [ 1, 14 @@ -124,7 +119,6 @@ 1, 19 ], - "filepath": "for-of-statement.js", "end": [ 1, 25 @@ -135,7 +129,6 @@ 1, 18 ], - "filepath": "for-of-statement.js", "end": [ 1, 23 @@ -154,7 +147,6 @@ 1, 37 ], - "filepath": "for-of-statement.js", "end": [ 1, 42 @@ -165,7 +157,6 @@ 1, 35 ], - "filepath": "for-of-statement.js", "end": [ 1, 39 @@ -183,9 +174,9 @@ "filePaths": [ "for-of-statement.js" ], - "sha1": "cf9ed207fbbfb8cb068aedf35c5a7d1c95440d06", + "sha1": "764b4aec6e49bf027190ab1e5083bdd35a055279", "gitDir": "test/corpus/repos/javascript", - "sha2": "303102430bf2d88d6da7137cc5571aeef5f93224" + "sha2": "ed8939173ee392ec35dd13ff8fee4d4c6f93f985" } ,{ "testCaseDescription": "javascript-for-of-statement-replacement-test", @@ -200,7 +191,6 @@ 1, 10 ], - "filepath": "for-of-statement.js", "end": [ 1, 14 @@ -211,7 +201,6 @@ 1, 10 ], - "filepath": "for-of-statement.js", "end": [ 1, 15 @@ -230,7 +219,6 @@ 1, 18 ], - "filepath": "for-of-statement.js", "end": [ 1, 23 @@ -241,7 +229,6 @@ 1, 19 ], - "filepath": "for-of-statement.js", "end": [ 1, 25 @@ -260,7 +247,6 @@ 1, 35 ], - "filepath": "for-of-statement.js", "end": [ 1, 39 @@ -271,7 +257,6 @@ 1, 37 ], - "filepath": "for-of-statement.js", "end": [ 1, 42 @@ -289,9 +274,9 @@ "filePaths": [ "for-of-statement.js" ], - "sha1": "303102430bf2d88d6da7137cc5571aeef5f93224", + "sha1": "ed8939173ee392ec35dd13ff8fee4d4c6f93f985", "gitDir": "test/corpus/repos/javascript", - "sha2": "01a95973305ffa51292ab7a8a0970f690c1937e3" + "sha2": "8be63f36f0484ba36f2de2a06801fe411b1b6bbc" } ,{ "testCaseDescription": "javascript-for-of-statement-delete-replacement-test", @@ -305,7 +290,6 @@ 1, 1 ], - "filepath": "for-of-statement.js", "end": [ 1, 46 @@ -322,7 +306,6 @@ 2, 1 ], - "filepath": "for-of-statement.js", "end": [ 2, 43 @@ -339,7 +322,6 @@ 2, 1 ], - "filepath": "for-of-statement.js", "end": [ 2, 46 @@ -356,9 +338,9 @@ "filePaths": [ "for-of-statement.js" ], - "sha1": "01a95973305ffa51292ab7a8a0970f690c1937e3", + "sha1": "8be63f36f0484ba36f2de2a06801fe411b1b6bbc", "gitDir": "test/corpus/repos/javascript", - "sha2": "84ebc837b7c11ee0b16b688e1029a411a3fd7327" + "sha2": "ae793daccac506e88da2f1d9e5bbe6a63f0c57e8" } ,{ "testCaseDescription": "javascript-for-of-statement-delete-test", @@ -372,7 +354,6 @@ 1, 1 ], - "filepath": "for-of-statement.js", "end": [ 1, 43 @@ -389,9 +370,9 @@ "filePaths": [ "for-of-statement.js" ], - "sha1": "84ebc837b7c11ee0b16b688e1029a411a3fd7327", + "sha1": "ae793daccac506e88da2f1d9e5bbe6a63f0c57e8", "gitDir": "test/corpus/repos/javascript", - "sha2": "710ddea57e61c8fe5d105dd26e5192efa8bd3e52" + "sha2": "99cbdc5330a41c478311d2cdf679409e67ebb255" } ,{ "testCaseDescription": "javascript-for-of-statement-delete-rest-test", @@ -405,7 +386,6 @@ 1, 1 ], - "filepath": "for-of-statement.js", "end": [ 1, 46 @@ -422,7 +402,7 @@ "filePaths": [ "for-of-statement.js" ], - "sha1": "710ddea57e61c8fe5d105dd26e5192efa8bd3e52", + "sha1": "99cbdc5330a41c478311d2cdf679409e67ebb255", "gitDir": "test/corpus/repos/javascript", - "sha2": "9f4f05255cc1f41d2c7dcbe4a450082306db1db1" + "sha2": "c1166aa59e4b025c51e2a166a47413eba325ff1d" }] diff --git a/test/corpus/diff-summaries/javascript/for-statement.json b/test/corpus/diff-summaries/javascript/for-statement.json index 65dd2ee27..09203b51e 100644 --- a/test/corpus/diff-summaries/javascript/for-statement.json +++ b/test/corpus/diff-summaries/javascript/for-statement.json @@ -10,7 +10,6 @@ 1, 1 ], - "filepath": "for-statement.js", "end": [ 1, 45 @@ -27,9 +26,9 @@ "filePaths": [ "for-statement.js" ], - "sha1": "acf5deeacb1725969d9840d8f43633df395e5dcc", + "sha1": "758306debb6130fc8710a0ff09833d692791db56", "gitDir": "test/corpus/repos/javascript", - "sha2": "b4ea2eb7e7467a4c031c09119af6d416b3e55f49" + "sha2": "00bf00e6840e200b9b83516547c531a2ff3898b1" } ,{ "testCaseDescription": "javascript-for-statement-replacement-insert-test", @@ -43,7 +42,6 @@ 1, 1 ], - "filepath": "for-statement.js", "end": [ 1, 46 @@ -60,7 +58,6 @@ 2, 1 ], - "filepath": "for-statement.js", "end": [ 2, 45 @@ -77,9 +74,9 @@ "filePaths": [ "for-statement.js" ], - "sha1": "b4ea2eb7e7467a4c031c09119af6d416b3e55f49", + "sha1": "00bf00e6840e200b9b83516547c531a2ff3898b1", "gitDir": "test/corpus/repos/javascript", - "sha2": "42294a27e6ced37446ae149fe6d4fe1e8713f0ce" + "sha2": "0b2091d8a227a635eb9bb3aa3ce14b284b77180a" } ,{ "testCaseDescription": "javascript-for-statement-delete-insert-test", @@ -94,7 +91,6 @@ 1, 25 ], - "filepath": "for-statement.js", "end": [ 1, 28 @@ -105,7 +101,6 @@ 1, 25 ], - "filepath": "for-statement.js", "end": [ 1, 27 @@ -123,9 +118,9 @@ "filePaths": [ "for-statement.js" ], - "sha1": "42294a27e6ced37446ae149fe6d4fe1e8713f0ce", + "sha1": "0b2091d8a227a635eb9bb3aa3ce14b284b77180a", "gitDir": "test/corpus/repos/javascript", - "sha2": "855efe1b8ab94118d9dc81c7ddf51cf2fb7e2cd8" + "sha2": "27c0f25dae543a46ab393cf49fc8202434805502" } ,{ "testCaseDescription": "javascript-for-statement-replacement-test", @@ -140,7 +135,6 @@ 1, 25 ], - "filepath": "for-statement.js", "end": [ 1, 27 @@ -151,7 +145,6 @@ 1, 25 ], - "filepath": "for-statement.js", "end": [ 1, 28 @@ -169,9 +162,9 @@ "filePaths": [ "for-statement.js" ], - "sha1": "855efe1b8ab94118d9dc81c7ddf51cf2fb7e2cd8", + "sha1": "27c0f25dae543a46ab393cf49fc8202434805502", "gitDir": "test/corpus/repos/javascript", - "sha2": "0e3c120db3320242ac9708e58766044b4368384f" + "sha2": "7696ee1c7f9e18ee1117c40c2d37d07a11f1f5df" } ,{ "testCaseDescription": "javascript-for-statement-delete-replacement-test", @@ -185,7 +178,6 @@ 1, 1 ], - "filepath": "for-statement.js", "end": [ 1, 46 @@ -202,7 +194,6 @@ 2, 1 ], - "filepath": "for-statement.js", "end": [ 2, 45 @@ -219,7 +210,6 @@ 2, 1 ], - "filepath": "for-statement.js", "end": [ 2, 46 @@ -236,9 +226,9 @@ "filePaths": [ "for-statement.js" ], - "sha1": "0e3c120db3320242ac9708e58766044b4368384f", + "sha1": "7696ee1c7f9e18ee1117c40c2d37d07a11f1f5df", "gitDir": "test/corpus/repos/javascript", - "sha2": "7f57c36ed55059e5b54ed4beeb937e9411756444" + "sha2": "4a93852bc579797f9f5de1e47fce59cfc8b2497f" } ,{ "testCaseDescription": "javascript-for-statement-delete-test", @@ -252,7 +242,6 @@ 1, 1 ], - "filepath": "for-statement.js", "end": [ 1, 45 @@ -269,9 +258,9 @@ "filePaths": [ "for-statement.js" ], - "sha1": "7f57c36ed55059e5b54ed4beeb937e9411756444", + "sha1": "4a93852bc579797f9f5de1e47fce59cfc8b2497f", "gitDir": "test/corpus/repos/javascript", - "sha2": "a4662a8658ee663b20534542a0681c83c1bf5dff" + "sha2": "c1968c262d5b3c83c9187948709acbbc9f620462" } ,{ "testCaseDescription": "javascript-for-statement-delete-rest-test", @@ -285,7 +274,6 @@ 1, 1 ], - "filepath": "for-statement.js", "end": [ 1, 46 @@ -302,7 +290,7 @@ "filePaths": [ "for-statement.js" ], - "sha1": "a4662a8658ee663b20534542a0681c83c1bf5dff", + "sha1": "c1968c262d5b3c83c9187948709acbbc9f620462", "gitDir": "test/corpus/repos/javascript", - "sha2": "0ee5df2573a8439ceee6c04faf15813932be3ad0" + "sha2": "d7c7a2ed324c7355ba6fc63705b6b879afd92c14" }] diff --git a/test/corpus/diff-summaries/javascript/function-call-args.json b/test/corpus/diff-summaries/javascript/function-call-args.json index 43fb9c66a..7b7b03051 100644 --- a/test/corpus/diff-summaries/javascript/function-call-args.json +++ b/test/corpus/diff-summaries/javascript/function-call-args.json @@ -10,7 +10,6 @@ 1, 1 ], - "filepath": "function-call-args.js", "end": [ 1, 77 @@ -27,9 +26,9 @@ "filePaths": [ "function-call-args.js" ], - "sha1": "ba35b41bf9e5b77b55af13c5001569dc5ce4ae9b", + "sha1": "39371fc387de287b5fed01670ecb6d42834d9558", "gitDir": "test/corpus/repos/javascript", - "sha2": "1c580a0a696dcd65629669d895b25cf9b33b916d" + "sha2": "b7a3a181908a1f263066ded0b6ffd54f76caf38f" } ,{ "testCaseDescription": "javascript-function-call-args-replacement-insert-test", @@ -43,7 +42,6 @@ 1, 1 ], - "filepath": "function-call-args.js", "end": [ 1, 83 @@ -60,7 +58,6 @@ 2, 1 ], - "filepath": "function-call-args.js", "end": [ 2, 77 @@ -77,9 +74,9 @@ "filePaths": [ "function-call-args.js" ], - "sha1": "1c580a0a696dcd65629669d895b25cf9b33b916d", + "sha1": "b7a3a181908a1f263066ded0b6ffd54f76caf38f", "gitDir": "test/corpus/repos/javascript", - "sha2": "37d7671c747ae91a15a4db8206eb008887ec0dc0" + "sha2": "c0233e25160450709ba8e3b1e9b3c728816e329f" } ,{ "testCaseDescription": "javascript-function-call-args-delete-insert-test", @@ -94,7 +91,6 @@ 1, 17 ], - "filepath": "function-call-args.js", "end": [ 1, 30 @@ -105,7 +101,6 @@ 1, 17 ], - "filepath": "function-call-args.js", "end": [ 1, 25 @@ -124,7 +119,6 @@ 1, 41 ], - "filepath": "function-call-args.js", "end": [ 1, 42 @@ -135,7 +129,6 @@ 1, 36 ], - "filepath": "function-call-args.js", "end": [ 1, 37 @@ -154,7 +147,6 @@ 1, 43 ], - "filepath": "function-call-args.js", "end": [ 1, 44 @@ -165,7 +157,6 @@ 1, 38 ], - "filepath": "function-call-args.js", "end": [ 1, 39 @@ -184,7 +175,6 @@ 1, 60 ], - "filepath": "function-call-args.js", "end": [ 1, 61 @@ -195,7 +185,6 @@ 1, 55 ], - "filepath": "function-call-args.js", "end": [ 1, 56 @@ -214,7 +203,6 @@ 1, 71 ], - "filepath": "function-call-args.js", "end": [ 1, 72 @@ -225,7 +213,6 @@ 1, 66 ], - "filepath": "function-call-args.js", "end": [ 1, 67 @@ -244,7 +231,6 @@ 1, 77 ], - "filepath": "function-call-args.js", "end": [ 1, 82 @@ -255,7 +241,6 @@ 1, 72 ], - "filepath": "function-call-args.js", "end": [ 1, 76 @@ -273,9 +258,9 @@ "filePaths": [ "function-call-args.js" ], - "sha1": "37d7671c747ae91a15a4db8206eb008887ec0dc0", + "sha1": "c0233e25160450709ba8e3b1e9b3c728816e329f", "gitDir": "test/corpus/repos/javascript", - "sha2": "d80ca9032224d374f339789c317c4ec463d87ffd" + "sha2": "ec2a13df058c25b9f4e873aeef08c968213e3a30" } ,{ "testCaseDescription": "javascript-function-call-args-replacement-test", @@ -290,7 +275,6 @@ 1, 17 ], - "filepath": "function-call-args.js", "end": [ 1, 25 @@ -301,7 +285,6 @@ 1, 17 ], - "filepath": "function-call-args.js", "end": [ 1, 30 @@ -320,7 +303,6 @@ 1, 36 ], - "filepath": "function-call-args.js", "end": [ 1, 37 @@ -331,7 +313,6 @@ 1, 41 ], - "filepath": "function-call-args.js", "end": [ 1, 42 @@ -350,7 +331,6 @@ 1, 38 ], - "filepath": "function-call-args.js", "end": [ 1, 39 @@ -361,7 +341,6 @@ 1, 43 ], - "filepath": "function-call-args.js", "end": [ 1, 44 @@ -380,7 +359,6 @@ 1, 55 ], - "filepath": "function-call-args.js", "end": [ 1, 56 @@ -391,7 +369,6 @@ 1, 60 ], - "filepath": "function-call-args.js", "end": [ 1, 61 @@ -410,7 +387,6 @@ 1, 66 ], - "filepath": "function-call-args.js", "end": [ 1, 67 @@ -421,7 +397,6 @@ 1, 71 ], - "filepath": "function-call-args.js", "end": [ 1, 72 @@ -440,7 +415,6 @@ 1, 72 ], - "filepath": "function-call-args.js", "end": [ 1, 76 @@ -451,7 +425,6 @@ 1, 77 ], - "filepath": "function-call-args.js", "end": [ 1, 82 @@ -469,9 +442,9 @@ "filePaths": [ "function-call-args.js" ], - "sha1": "d80ca9032224d374f339789c317c4ec463d87ffd", + "sha1": "ec2a13df058c25b9f4e873aeef08c968213e3a30", "gitDir": "test/corpus/repos/javascript", - "sha2": "0d41fd486d6c0a7c2b91fdd55d127daf10891111" + "sha2": "2a065e7cc65868acd59182dd9ee7aa71f581be6f" } ,{ "testCaseDescription": "javascript-function-call-args-delete-replacement-test", @@ -485,7 +458,6 @@ 1, 1 ], - "filepath": "function-call-args.js", "end": [ 1, 83 @@ -502,7 +474,6 @@ 2, 1 ], - "filepath": "function-call-args.js", "end": [ 2, 77 @@ -519,7 +490,6 @@ 2, 1 ], - "filepath": "function-call-args.js", "end": [ 2, 83 @@ -536,9 +506,9 @@ "filePaths": [ "function-call-args.js" ], - "sha1": "0d41fd486d6c0a7c2b91fdd55d127daf10891111", + "sha1": "2a065e7cc65868acd59182dd9ee7aa71f581be6f", "gitDir": "test/corpus/repos/javascript", - "sha2": "405a56558fe628c54165e1605db4f9f436150998" + "sha2": "b56a80a0b9ce5ff95b4ec2417ff4770ac5d7d5b5" } ,{ "testCaseDescription": "javascript-function-call-args-delete-test", @@ -552,7 +522,6 @@ 1, 1 ], - "filepath": "function-call-args.js", "end": [ 1, 77 @@ -569,9 +538,9 @@ "filePaths": [ "function-call-args.js" ], - "sha1": "405a56558fe628c54165e1605db4f9f436150998", + "sha1": "b56a80a0b9ce5ff95b4ec2417ff4770ac5d7d5b5", "gitDir": "test/corpus/repos/javascript", - "sha2": "2d4b12df03d51a643ac94375906d6b162cfbf3ce" + "sha2": "202a515a4ca63fa61a58a82ea1d5bcd10515da8c" } ,{ "testCaseDescription": "javascript-function-call-args-delete-rest-test", @@ -585,7 +554,6 @@ 1, 1 ], - "filepath": "function-call-args.js", "end": [ 1, 83 @@ -602,7 +570,7 @@ "filePaths": [ "function-call-args.js" ], - "sha1": "2d4b12df03d51a643ac94375906d6b162cfbf3ce", + "sha1": "202a515a4ca63fa61a58a82ea1d5bcd10515da8c", "gitDir": "test/corpus/repos/javascript", - "sha2": "e77e93003c7650329a3f14274c85d9ce07ba9273" + "sha2": "989abe2f89480b24702666d42becea8aa3dd9356" }] diff --git a/test/corpus/diff-summaries/javascript/function-call.json b/test/corpus/diff-summaries/javascript/function-call.json index 2d1da220e..9c1b4df40 100644 --- a/test/corpus/diff-summaries/javascript/function-call.json +++ b/test/corpus/diff-summaries/javascript/function-call.json @@ -10,7 +10,6 @@ 1, 1 ], - "filepath": "function-call.js", "end": [ 1, 27 @@ -27,9 +26,9 @@ "filePaths": [ "function-call.js" ], - "sha1": "4eca89a41a58f273d4b0819fde38f18c1f8e8021", + "sha1": "2920543b3620bcf0c44e9f14e9b9173b7ffaaf74", "gitDir": "test/corpus/repos/javascript", - "sha2": "92c1472cd33095ff48619ee70f121124b0824982" + "sha2": "7fb60101d44227f815b26e0ddf7192c814147c0a" } ,{ "testCaseDescription": "javascript-function-call-replacement-insert-test", @@ -43,7 +42,6 @@ 1, 1 ], - "filepath": "function-call.js", "end": [ 1, 27 @@ -60,7 +58,6 @@ 2, 1 ], - "filepath": "function-call.js", "end": [ 2, 27 @@ -77,9 +74,9 @@ "filePaths": [ "function-call.js" ], - "sha1": "92c1472cd33095ff48619ee70f121124b0824982", + "sha1": "7fb60101d44227f815b26e0ddf7192c814147c0a", "gitDir": "test/corpus/repos/javascript", - "sha2": "3d1432206f287820e06179320645a20bc044e0cd" + "sha2": "b8ef71202991eb150947127c3d627dfefbfb9cbd" } ,{ "testCaseDescription": "javascript-function-call-delete-insert-test", @@ -94,7 +91,6 @@ 1, 20 ], - "filepath": "function-call.js", "end": [ 1, 26 @@ -105,7 +101,6 @@ 1, 20 ], - "filepath": "function-call.js", "end": [ 1, 26 @@ -123,9 +118,9 @@ "filePaths": [ "function-call.js" ], - "sha1": "3d1432206f287820e06179320645a20bc044e0cd", + "sha1": "b8ef71202991eb150947127c3d627dfefbfb9cbd", "gitDir": "test/corpus/repos/javascript", - "sha2": "d12a8afd790463d0f757c83c263cf0edd9d827c7" + "sha2": "1c6634e5803e9eae248fb104c87d95b7ca4911f3" } ,{ "testCaseDescription": "javascript-function-call-replacement-test", @@ -140,7 +135,6 @@ 1, 20 ], - "filepath": "function-call.js", "end": [ 1, 26 @@ -151,7 +145,6 @@ 1, 20 ], - "filepath": "function-call.js", "end": [ 1, 26 @@ -169,9 +162,9 @@ "filePaths": [ "function-call.js" ], - "sha1": "d12a8afd790463d0f757c83c263cf0edd9d827c7", + "sha1": "1c6634e5803e9eae248fb104c87d95b7ca4911f3", "gitDir": "test/corpus/repos/javascript", - "sha2": "6587722b506d7a8ceae803f9e5f7b0d8f0958401" + "sha2": "89d68d8b51fcfcf79005c5616ee95351c6eb9d61" } ,{ "testCaseDescription": "javascript-function-call-delete-replacement-test", @@ -185,7 +178,6 @@ 1, 1 ], - "filepath": "function-call.js", "end": [ 1, 27 @@ -202,7 +194,6 @@ 2, 1 ], - "filepath": "function-call.js", "end": [ 2, 27 @@ -219,7 +210,6 @@ 2, 1 ], - "filepath": "function-call.js", "end": [ 2, 27 @@ -236,9 +226,9 @@ "filePaths": [ "function-call.js" ], - "sha1": "6587722b506d7a8ceae803f9e5f7b0d8f0958401", + "sha1": "89d68d8b51fcfcf79005c5616ee95351c6eb9d61", "gitDir": "test/corpus/repos/javascript", - "sha2": "c54c453d06597281a9e92b21dadc3a6672f717ad" + "sha2": "25b62ac788457989d53e49e35e947be2120e91d4" } ,{ "testCaseDescription": "javascript-function-call-delete-test", @@ -252,7 +242,6 @@ 1, 1 ], - "filepath": "function-call.js", "end": [ 1, 27 @@ -269,9 +258,9 @@ "filePaths": [ "function-call.js" ], - "sha1": "c54c453d06597281a9e92b21dadc3a6672f717ad", + "sha1": "25b62ac788457989d53e49e35e947be2120e91d4", "gitDir": "test/corpus/repos/javascript", - "sha2": "11d88c653401dab427534d1e417f80aadf14db77" + "sha2": "d67336b7b60950bf99ef6777a6d25cd8a6cb57a6" } ,{ "testCaseDescription": "javascript-function-call-delete-rest-test", @@ -285,7 +274,6 @@ 1, 1 ], - "filepath": "function-call.js", "end": [ 1, 27 @@ -302,7 +290,7 @@ "filePaths": [ "function-call.js" ], - "sha1": "11d88c653401dab427534d1e417f80aadf14db77", + "sha1": "d67336b7b60950bf99ef6777a6d25cd8a6cb57a6", "gitDir": "test/corpus/repos/javascript", - "sha2": "d1d52518c72665ed2a4fee18636ce01a6be5ad1b" + "sha2": "b0e9ef95e61d208d86142a5e5682fe30ceb18c8b" }] diff --git a/test/corpus/diff-summaries/javascript/function.json b/test/corpus/diff-summaries/javascript/function.json index 5013ae913..efa80ebab 100644 --- a/test/corpus/diff-summaries/javascript/function.json +++ b/test/corpus/diff-summaries/javascript/function.json @@ -10,7 +10,6 @@ 1, 1 ], - "filepath": "function.js", "end": [ 1, 31 @@ -27,9 +26,9 @@ "filePaths": [ "function.js" ], - "sha1": "8eef7adcdbe1c08c7b39e24ab94c0aa76c2169dc", + "sha1": "67cbf8843e0286f8dda242b238d30efab57d6790", "gitDir": "test/corpus/repos/javascript", - "sha2": "25c303e8d46dbc99249691a4f520e088898f172f" + "sha2": "2717b5aa509e14dfd94842eea00ca66111a015be" } ,{ "testCaseDescription": "javascript-function-replacement-insert-test", @@ -43,7 +42,6 @@ 1, 1 ], - "filepath": "function.js", "end": [ 1, 31 @@ -60,7 +58,6 @@ 2, 1 ], - "filepath": "function.js", "end": [ 2, 31 @@ -77,9 +74,9 @@ "filePaths": [ "function.js" ], - "sha1": "25c303e8d46dbc99249691a4f520e088898f172f", + "sha1": "2717b5aa509e14dfd94842eea00ca66111a015be", "gitDir": "test/corpus/repos/javascript", - "sha2": "06bc1c8774b7ffae8922e09394c8ca488ac64a3c" + "sha2": "f98962b37651faa3154d25fe2828a12df02992d8" } ,{ "testCaseDescription": "javascript-function-delete-insert-test", @@ -94,7 +91,6 @@ 1, 24 ], - "filepath": "function.js", "end": [ 1, 28 @@ -105,7 +101,6 @@ 1, 24 ], - "filepath": "function.js", "end": [ 1, 28 @@ -123,9 +118,9 @@ "filePaths": [ "function.js" ], - "sha1": "06bc1c8774b7ffae8922e09394c8ca488ac64a3c", + "sha1": "f98962b37651faa3154d25fe2828a12df02992d8", "gitDir": "test/corpus/repos/javascript", - "sha2": "c01a61822d751ee1358ad1d931c3407ab9ccef59" + "sha2": "2b9d37d0871a1c8f0a50842e50cab572f55d07db" } ,{ "testCaseDescription": "javascript-function-replacement-test", @@ -140,7 +135,6 @@ 1, 24 ], - "filepath": "function.js", "end": [ 1, 28 @@ -151,7 +145,6 @@ 1, 24 ], - "filepath": "function.js", "end": [ 1, 28 @@ -169,9 +162,9 @@ "filePaths": [ "function.js" ], - "sha1": "c01a61822d751ee1358ad1d931c3407ab9ccef59", + "sha1": "2b9d37d0871a1c8f0a50842e50cab572f55d07db", "gitDir": "test/corpus/repos/javascript", - "sha2": "72603cc1f191205b5110e07f79ad86dcd630d74e" + "sha2": "1bec33037691d4c4d97117aa1a1550a1a0d3113f" } ,{ "testCaseDescription": "javascript-function-delete-replacement-test", @@ -185,7 +178,6 @@ 1, 1 ], - "filepath": "function.js", "end": [ 1, 31 @@ -202,7 +194,6 @@ 2, 1 ], - "filepath": "function.js", "end": [ 2, 31 @@ -219,7 +210,6 @@ 2, 1 ], - "filepath": "function.js", "end": [ 2, 31 @@ -236,9 +226,9 @@ "filePaths": [ "function.js" ], - "sha1": "72603cc1f191205b5110e07f79ad86dcd630d74e", + "sha1": "1bec33037691d4c4d97117aa1a1550a1a0d3113f", "gitDir": "test/corpus/repos/javascript", - "sha2": "3e8c275ef0056b10b359e180e4d3f5317c04a5e4" + "sha2": "189c17d7869e4ec45865288472d5616e6f934389" } ,{ "testCaseDescription": "javascript-function-delete-test", @@ -252,7 +242,6 @@ 1, 1 ], - "filepath": "function.js", "end": [ 1, 31 @@ -269,9 +258,9 @@ "filePaths": [ "function.js" ], - "sha1": "3e8c275ef0056b10b359e180e4d3f5317c04a5e4", + "sha1": "189c17d7869e4ec45865288472d5616e6f934389", "gitDir": "test/corpus/repos/javascript", - "sha2": "f54c048b172ba9cbc7d77acccfd4f80173511b7a" + "sha2": "54e8366ab2c4558cf28dd50f6939ae84738caa6c" } ,{ "testCaseDescription": "javascript-function-delete-rest-test", @@ -285,7 +274,6 @@ 1, 1 ], - "filepath": "function.js", "end": [ 1, 31 @@ -302,7 +290,7 @@ "filePaths": [ "function.js" ], - "sha1": "f54c048b172ba9cbc7d77acccfd4f80173511b7a", + "sha1": "54e8366ab2c4558cf28dd50f6939ae84738caa6c", "gitDir": "test/corpus/repos/javascript", - "sha2": "15ff2677dbf6ef4e724df21936b1dec373b4c087" + "sha2": "ea75c493779d6c65e44c59733f6073e0be814d0b" }] diff --git a/test/corpus/diff-summaries/javascript/generator-function.json b/test/corpus/diff-summaries/javascript/generator-function.json index 430cf9fed..fd2584efb 100644 --- a/test/corpus/diff-summaries/javascript/generator-function.json +++ b/test/corpus/diff-summaries/javascript/generator-function.json @@ -10,7 +10,6 @@ 1, 1 ], - "filepath": "generator-function.js", "end": [ 1, 59 @@ -27,9 +26,9 @@ "filePaths": [ "generator-function.js" ], - "sha1": "64732c38069cc70ee3bea66306d966d902444b68", + "sha1": "4e58cc6cacea1897b6ba0b9d766f0ba965b0c8fa", "gitDir": "test/corpus/repos/javascript", - "sha2": "a34ad7fd0b70236787b11433577fbb0e40a7e208" + "sha2": "18a0e0a3a3ce01a9032d344cc27e74ceb4ca309f" } ,{ "testCaseDescription": "javascript-generator-function-replacement-insert-test", @@ -43,7 +42,6 @@ 1, 1 ], - "filepath": "generator-function.js", "end": [ 1, 62 @@ -60,7 +58,6 @@ 2, 1 ], - "filepath": "generator-function.js", "end": [ 2, 59 @@ -77,9 +74,9 @@ "filePaths": [ "generator-function.js" ], - "sha1": "a34ad7fd0b70236787b11433577fbb0e40a7e208", + "sha1": "18a0e0a3a3ce01a9032d344cc27e74ceb4ca309f", "gitDir": "test/corpus/repos/javascript", - "sha2": "620959c65bb56fb7111b587d612af03547182987" + "sha2": "23285112861e1d2fe617efdb23c5d51bf4075224" } ,{ "testCaseDescription": "javascript-generator-function-delete-insert-test", @@ -94,7 +91,6 @@ 1, 11 ], - "filepath": "generator-function.js", "end": [ 1, 27 @@ -105,7 +101,6 @@ 1, 11 ], - "filepath": "generator-function.js", "end": [ 1, 24 @@ -123,9 +118,9 @@ "filePaths": [ "generator-function.js" ], - "sha1": "620959c65bb56fb7111b587d612af03547182987", + "sha1": "23285112861e1d2fe617efdb23c5d51bf4075224", "gitDir": "test/corpus/repos/javascript", - "sha2": "a2eb2702e26ae6d4fabaff49b6afe20f5ab7e7e3" + "sha2": "3cd99e8cbe1ba540886b65b6921ec1cf01fb79ca" } ,{ "testCaseDescription": "javascript-generator-function-replacement-test", @@ -140,7 +135,6 @@ 1, 11 ], - "filepath": "generator-function.js", "end": [ 1, 24 @@ -151,7 +145,6 @@ 1, 11 ], - "filepath": "generator-function.js", "end": [ 1, 27 @@ -169,9 +162,9 @@ "filePaths": [ "generator-function.js" ], - "sha1": "a2eb2702e26ae6d4fabaff49b6afe20f5ab7e7e3", + "sha1": "3cd99e8cbe1ba540886b65b6921ec1cf01fb79ca", "gitDir": "test/corpus/repos/javascript", - "sha2": "43156dff1c85bedb4bcc8cc0467ab3621b43e685" + "sha2": "afe62cf42a38e09a30d1e289c2197445039c4d8b" } ,{ "testCaseDescription": "javascript-generator-function-delete-replacement-test", @@ -185,7 +178,6 @@ 1, 1 ], - "filepath": "generator-function.js", "end": [ 1, 62 @@ -202,7 +194,6 @@ 2, 1 ], - "filepath": "generator-function.js", "end": [ 2, 59 @@ -219,7 +210,6 @@ 2, 1 ], - "filepath": "generator-function.js", "end": [ 2, 62 @@ -236,9 +226,9 @@ "filePaths": [ "generator-function.js" ], - "sha1": "43156dff1c85bedb4bcc8cc0467ab3621b43e685", + "sha1": "afe62cf42a38e09a30d1e289c2197445039c4d8b", "gitDir": "test/corpus/repos/javascript", - "sha2": "8253ea0f958328699c263ea46ece386d55ea46d5" + "sha2": "b8554280a32f48d22eff39b921432c8148f2e602" } ,{ "testCaseDescription": "javascript-generator-function-delete-test", @@ -252,7 +242,6 @@ 1, 1 ], - "filepath": "generator-function.js", "end": [ 1, 59 @@ -269,9 +258,9 @@ "filePaths": [ "generator-function.js" ], - "sha1": "8253ea0f958328699c263ea46ece386d55ea46d5", + "sha1": "b8554280a32f48d22eff39b921432c8148f2e602", "gitDir": "test/corpus/repos/javascript", - "sha2": "2ff3ccf6c80c2aec6fe592160e3ed97fcbbfcbe5" + "sha2": "015cdf9ee2145bcf4de97926d0df3d30f5f4b23e" } ,{ "testCaseDescription": "javascript-generator-function-delete-rest-test", @@ -285,7 +274,6 @@ 1, 1 ], - "filepath": "generator-function.js", "end": [ 1, 62 @@ -302,7 +290,7 @@ "filePaths": [ "generator-function.js" ], - "sha1": "2ff3ccf6c80c2aec6fe592160e3ed97fcbbfcbe5", + "sha1": "015cdf9ee2145bcf4de97926d0df3d30f5f4b23e", "gitDir": "test/corpus/repos/javascript", - "sha2": "4f10daadd1f0292f7909951043926535151b0c5d" + "sha2": "bb0f797d0ecd6410261347f4bb4a9d7ec2dbd9e8" }] diff --git a/test/corpus/diff-summaries/javascript/identifier.json b/test/corpus/diff-summaries/javascript/identifier.json index c9447716a..553b940e7 100644 --- a/test/corpus/diff-summaries/javascript/identifier.json +++ b/test/corpus/diff-summaries/javascript/identifier.json @@ -10,7 +10,6 @@ 1, 1 ], - "filepath": "identifier.js", "end": [ 1, 7 @@ -27,9 +26,9 @@ "filePaths": [ "identifier.js" ], - "sha1": "d284f40259b610bfb02c24b4693ef24e5f303e86", + "sha1": "326c0b42a3c17cfb9c231515f4cbe3c81c621f1c", "gitDir": "test/corpus/repos/javascript", - "sha2": "dabdbabd7ba1526716d469c78c10f9737b47d01c" + "sha2": "820fa9e9590b2599eceae072c5f58cdbdb9a537c" } ,{ "testCaseDescription": "javascript-identifier-replacement-insert-test", @@ -43,7 +42,6 @@ 1, 1 ], - "filepath": "identifier.js", "end": [ 1, 8 @@ -60,7 +58,6 @@ 2, 1 ], - "filepath": "identifier.js", "end": [ 2, 7 @@ -77,9 +74,9 @@ "filePaths": [ "identifier.js" ], - "sha1": "dabdbabd7ba1526716d469c78c10f9737b47d01c", + "sha1": "820fa9e9590b2599eceae072c5f58cdbdb9a537c", "gitDir": "test/corpus/repos/javascript", - "sha2": "941b3f8591a3ba18973481f416050bda8b357c2b" + "sha2": "2d5f6d80071c263cbc273856778d3251ce74517f" } ,{ "testCaseDescription": "javascript-identifier-delete-insert-test", @@ -94,7 +91,6 @@ 1, 1 ], - "filepath": "identifier.js", "end": [ 1, 8 @@ -105,7 +101,6 @@ 1, 1 ], - "filepath": "identifier.js", "end": [ 1, 7 @@ -123,9 +118,9 @@ "filePaths": [ "identifier.js" ], - "sha1": "941b3f8591a3ba18973481f416050bda8b357c2b", + "sha1": "2d5f6d80071c263cbc273856778d3251ce74517f", "gitDir": "test/corpus/repos/javascript", - "sha2": "db4dc209656d906ff5981039a5d73cd5a8d69260" + "sha2": "3f31f4a9c07a65eb2798133713f2f34fcee799c8" } ,{ "testCaseDescription": "javascript-identifier-replacement-test", @@ -140,7 +135,6 @@ 1, 1 ], - "filepath": "identifier.js", "end": [ 1, 7 @@ -151,7 +145,6 @@ 1, 1 ], - "filepath": "identifier.js", "end": [ 1, 8 @@ -169,9 +162,9 @@ "filePaths": [ "identifier.js" ], - "sha1": "db4dc209656d906ff5981039a5d73cd5a8d69260", + "sha1": "3f31f4a9c07a65eb2798133713f2f34fcee799c8", "gitDir": "test/corpus/repos/javascript", - "sha2": "06f578ead4766ba168235bde73ed44eed1dcd3c2" + "sha2": "fd58b769ec4b48c0bee68cfe834c8bb1adcdb516" } ,{ "testCaseDescription": "javascript-identifier-delete-replacement-test", @@ -185,7 +178,6 @@ 1, 1 ], - "filepath": "identifier.js", "end": [ 1, 8 @@ -202,7 +194,6 @@ 2, 1 ], - "filepath": "identifier.js", "end": [ 2, 7 @@ -219,7 +210,6 @@ 2, 1 ], - "filepath": "identifier.js", "end": [ 2, 8 @@ -236,9 +226,9 @@ "filePaths": [ "identifier.js" ], - "sha1": "06f578ead4766ba168235bde73ed44eed1dcd3c2", + "sha1": "fd58b769ec4b48c0bee68cfe834c8bb1adcdb516", "gitDir": "test/corpus/repos/javascript", - "sha2": "060798e5d93e623ed5b941f4352826f1238b4ebd" + "sha2": "2a566f75e47f4106c9d875d7090b32ba869ed332" } ,{ "testCaseDescription": "javascript-identifier-delete-test", @@ -252,7 +242,6 @@ 1, 1 ], - "filepath": "identifier.js", "end": [ 1, 7 @@ -269,9 +258,9 @@ "filePaths": [ "identifier.js" ], - "sha1": "060798e5d93e623ed5b941f4352826f1238b4ebd", + "sha1": "2a566f75e47f4106c9d875d7090b32ba869ed332", "gitDir": "test/corpus/repos/javascript", - "sha2": "9b4f87f5191a1690b9f4f4c381e1c43dc9158905" + "sha2": "ebe92c64b9f8a0a4b422493d741cff603d82974b" } ,{ "testCaseDescription": "javascript-identifier-delete-rest-test", @@ -285,7 +274,6 @@ 1, 1 ], - "filepath": "identifier.js", "end": [ 1, 8 @@ -302,7 +290,7 @@ "filePaths": [ "identifier.js" ], - "sha1": "9b4f87f5191a1690b9f4f4c381e1c43dc9158905", + "sha1": "ebe92c64b9f8a0a4b422493d741cff603d82974b", "gitDir": "test/corpus/repos/javascript", - "sha2": "a0b31feb22c899b106e153d1abbe125b102e7ddb" + "sha2": "35dca27c6725f2defede78609517066c5e1b30dc" }] diff --git a/test/corpus/diff-summaries/javascript/if-else.json b/test/corpus/diff-summaries/javascript/if-else.json index dd7331662..66f27ec0d 100644 --- a/test/corpus/diff-summaries/javascript/if-else.json +++ b/test/corpus/diff-summaries/javascript/if-else.json @@ -10,7 +10,6 @@ 1, 1 ], - "filepath": "if-else.js", "end": [ 1, 25 @@ -27,9 +26,9 @@ "filePaths": [ "if-else.js" ], - "sha1": "b5989e3686427410aa40bbed9fb40c02cfd7f744", + "sha1": "9791d662a9cbd0fe8d9219fcf7550a3417954956", "gitDir": "test/corpus/repos/javascript", - "sha2": "725697b100be9f7edd86b00e224283a91cbd8fa2" + "sha2": "7af553e3a57c0d33f2c020598c2f05db9398f594" } ,{ "testCaseDescription": "javascript-if-else-replacement-insert-test", @@ -43,7 +42,6 @@ 1, 1 ], - "filepath": "if-else.js", "end": [ 1, 29 @@ -60,7 +58,6 @@ 2, 1 ], - "filepath": "if-else.js", "end": [ 2, 25 @@ -77,9 +74,9 @@ "filePaths": [ "if-else.js" ], - "sha1": "725697b100be9f7edd86b00e224283a91cbd8fa2", + "sha1": "7af553e3a57c0d33f2c020598c2f05db9398f594", "gitDir": "test/corpus/repos/javascript", - "sha2": "2936d381fe9a288e033a0ccb74059fefbc713e61" + "sha2": "651c15bb59c428793be04e7072f6d137832df250" } ,{ "testCaseDescription": "javascript-if-else-delete-insert-test", @@ -94,7 +91,6 @@ 1, 1 ], - "filepath": "if-else.js", "end": [ 1, 29 @@ -105,7 +101,6 @@ 1, 1 ], - "filepath": "if-else.js", "end": [ 1, 25 @@ -123,9 +118,9 @@ "filePaths": [ "if-else.js" ], - "sha1": "2936d381fe9a288e033a0ccb74059fefbc713e61", + "sha1": "651c15bb59c428793be04e7072f6d137832df250", "gitDir": "test/corpus/repos/javascript", - "sha2": "566015c74b44a5fb921493dcd74105208669a30e" + "sha2": "15b975c4d4e28f674c65de1da47ba66daafc29bf" } ,{ "testCaseDescription": "javascript-if-else-replacement-test", @@ -140,7 +135,6 @@ 1, 1 ], - "filepath": "if-else.js", "end": [ 1, 25 @@ -151,7 +145,6 @@ 1, 1 ], - "filepath": "if-else.js", "end": [ 1, 29 @@ -169,9 +162,9 @@ "filePaths": [ "if-else.js" ], - "sha1": "566015c74b44a5fb921493dcd74105208669a30e", + "sha1": "15b975c4d4e28f674c65de1da47ba66daafc29bf", "gitDir": "test/corpus/repos/javascript", - "sha2": "25631d5929d6e41a15ce75b232e7fe13ab079b16" + "sha2": "2ee5946e894b4aa6269be6efb6f47f568208cbba" } ,{ "testCaseDescription": "javascript-if-else-delete-replacement-test", @@ -185,7 +178,6 @@ 1, 1 ], - "filepath": "if-else.js", "end": [ 1, 29 @@ -202,7 +194,6 @@ 2, 1 ], - "filepath": "if-else.js", "end": [ 2, 25 @@ -219,7 +210,6 @@ 2, 1 ], - "filepath": "if-else.js", "end": [ 2, 29 @@ -236,9 +226,9 @@ "filePaths": [ "if-else.js" ], - "sha1": "25631d5929d6e41a15ce75b232e7fe13ab079b16", + "sha1": "2ee5946e894b4aa6269be6efb6f47f568208cbba", "gitDir": "test/corpus/repos/javascript", - "sha2": "23d834c70a8d2ce7d2bf4bbf8d9e7152a5e91e3c" + "sha2": "afba47fff506da21a377692c35e52c9777ffa56b" } ,{ "testCaseDescription": "javascript-if-else-delete-test", @@ -252,7 +242,6 @@ 1, 1 ], - "filepath": "if-else.js", "end": [ 1, 25 @@ -269,9 +258,9 @@ "filePaths": [ "if-else.js" ], - "sha1": "23d834c70a8d2ce7d2bf4bbf8d9e7152a5e91e3c", + "sha1": "afba47fff506da21a377692c35e52c9777ffa56b", "gitDir": "test/corpus/repos/javascript", - "sha2": "5ddde48f1e87c767f6992cedaab82d36e9d53d1e" + "sha2": "b8cf4deac8a619ffabbbb6619640509d2a12f6af" } ,{ "testCaseDescription": "javascript-if-else-delete-rest-test", @@ -285,7 +274,6 @@ 1, 1 ], - "filepath": "if-else.js", "end": [ 1, 29 @@ -302,7 +290,7 @@ "filePaths": [ "if-else.js" ], - "sha1": "5ddde48f1e87c767f6992cedaab82d36e9d53d1e", + "sha1": "b8cf4deac8a619ffabbbb6619640509d2a12f6af", "gitDir": "test/corpus/repos/javascript", - "sha2": "5e0220ed7ac30b0db50a637fd48230ca14da8570" + "sha2": "2d5d9ee14704ef70452e42e144662eceacdb562d" }] diff --git a/test/corpus/diff-summaries/javascript/if.json b/test/corpus/diff-summaries/javascript/if.json index df99b4e7f..860ad92b4 100644 --- a/test/corpus/diff-summaries/javascript/if.json +++ b/test/corpus/diff-summaries/javascript/if.json @@ -10,7 +10,6 @@ 1, 1 ], - "filepath": "if.js", "end": [ 1, 19 @@ -27,9 +26,9 @@ "filePaths": [ "if.js" ], - "sha1": "41251fa1af46b7fe46270fa62626832e6d95fb19", + "sha1": "019ed2c1f543531ab1678c9fcd7dd223ad5ca8b2", "gitDir": "test/corpus/repos/javascript", - "sha2": "2296d132422661e0653447473e8f4403e48291f5" + "sha2": "a4b4113212a03138f0546396dfb35170538bb846" } ,{ "testCaseDescription": "javascript-if-replacement-insert-test", @@ -43,7 +42,6 @@ 1, 1 ], - "filepath": "if.js", "end": [ 1, 24 @@ -60,7 +58,6 @@ 2, 1 ], - "filepath": "if.js", "end": [ 2, 19 @@ -77,9 +74,9 @@ "filePaths": [ "if.js" ], - "sha1": "2296d132422661e0653447473e8f4403e48291f5", + "sha1": "a4b4113212a03138f0546396dfb35170538bb846", "gitDir": "test/corpus/repos/javascript", - "sha2": "4946660306dd1613763a3878ac416172a16bf096" + "sha2": "874a29b843b633497b98f99ab606daa42e02402f" } ,{ "testCaseDescription": "javascript-if-delete-insert-test", @@ -94,7 +91,6 @@ 1, 1 ], - "filepath": "if.js", "end": [ 1, 24 @@ -105,7 +101,6 @@ 1, 1 ], - "filepath": "if.js", "end": [ 1, 19 @@ -123,9 +118,9 @@ "filePaths": [ "if.js" ], - "sha1": "4946660306dd1613763a3878ac416172a16bf096", + "sha1": "874a29b843b633497b98f99ab606daa42e02402f", "gitDir": "test/corpus/repos/javascript", - "sha2": "f434fd9424b590cbd12ee33a6e94cda6aa6d294f" + "sha2": "16128f22ec566f5acbb690d0ef838d6227cdd402" } ,{ "testCaseDescription": "javascript-if-replacement-test", @@ -140,7 +135,6 @@ 1, 1 ], - "filepath": "if.js", "end": [ 1, 19 @@ -151,7 +145,6 @@ 1, 1 ], - "filepath": "if.js", "end": [ 1, 24 @@ -169,9 +162,9 @@ "filePaths": [ "if.js" ], - "sha1": "f434fd9424b590cbd12ee33a6e94cda6aa6d294f", + "sha1": "16128f22ec566f5acbb690d0ef838d6227cdd402", "gitDir": "test/corpus/repos/javascript", - "sha2": "17b87e95a0d8e4e7b0aec67a484ffdcbebf57569" + "sha2": "9fd01fbbfa583c431e65fa74fb11ab8bfce478a5" } ,{ "testCaseDescription": "javascript-if-delete-replacement-test", @@ -185,7 +178,6 @@ 1, 1 ], - "filepath": "if.js", "end": [ 1, 24 @@ -202,7 +194,6 @@ 2, 1 ], - "filepath": "if.js", "end": [ 2, 19 @@ -219,7 +210,6 @@ 2, 1 ], - "filepath": "if.js", "end": [ 2, 24 @@ -236,9 +226,9 @@ "filePaths": [ "if.js" ], - "sha1": "17b87e95a0d8e4e7b0aec67a484ffdcbebf57569", + "sha1": "9fd01fbbfa583c431e65fa74fb11ab8bfce478a5", "gitDir": "test/corpus/repos/javascript", - "sha2": "0dcfdf6fe232a9e637d3dc0497ba871a901a8ee0" + "sha2": "e7e84a047077fb4d105e58efd5866b2ac0a4d12a" } ,{ "testCaseDescription": "javascript-if-delete-test", @@ -252,7 +242,6 @@ 1, 1 ], - "filepath": "if.js", "end": [ 1, 19 @@ -269,9 +258,9 @@ "filePaths": [ "if.js" ], - "sha1": "0dcfdf6fe232a9e637d3dc0497ba871a901a8ee0", + "sha1": "e7e84a047077fb4d105e58efd5866b2ac0a4d12a", "gitDir": "test/corpus/repos/javascript", - "sha2": "f6518bfc5eb2595212cf06ebd298df9b349c0c1b" + "sha2": "c026ca9c14269cbdaa6e276375c1e6a635e93067" } ,{ "testCaseDescription": "javascript-if-delete-rest-test", @@ -285,7 +274,6 @@ 1, 1 ], - "filepath": "if.js", "end": [ 1, 24 @@ -302,7 +290,7 @@ "filePaths": [ "if.js" ], - "sha1": "f6518bfc5eb2595212cf06ebd298df9b349c0c1b", + "sha1": "c026ca9c14269cbdaa6e276375c1e6a635e93067", "gitDir": "test/corpus/repos/javascript", - "sha2": "b5989e3686427410aa40bbed9fb40c02cfd7f744" + "sha2": "cb6ecdcdc2f19afb8b09b417b7b3789de92bbe2c" }] diff --git a/test/corpus/diff-summaries/javascript/import.json b/test/corpus/diff-summaries/javascript/import.json index b50e2c2d6..28e46ab35 100644 --- a/test/corpus/diff-summaries/javascript/import.json +++ b/test/corpus/diff-summaries/javascript/import.json @@ -10,7 +10,6 @@ 1, 1 ], - "filepath": "import.js", "end": [ 1, 33 @@ -27,7 +26,6 @@ 2, 1 ], - "filepath": "import.js", "end": [ 2, 34 @@ -44,7 +42,6 @@ 3, 1 ], - "filepath": "import.js", "end": [ 3, 30 @@ -61,7 +58,6 @@ 4, 1 ], - "filepath": "import.js", "end": [ 4, 46 @@ -78,7 +74,6 @@ 5, 1 ], - "filepath": "import.js", "end": [ 5, 57 @@ -95,7 +90,6 @@ 6, 1 ], - "filepath": "import.js", "end": [ 6, 70 @@ -112,7 +106,6 @@ 7, 1 ], - "filepath": "import.js", "end": [ 7, 50 @@ -129,7 +122,6 @@ 8, 1 ], - "filepath": "import.js", "end": [ 8, 22 @@ -146,9 +138,9 @@ "filePaths": [ "import.js" ], - "sha1": "1f335e06f911822dae7567bc5b0c2d07c78e08d7", + "sha1": "79e42f5e2d2b5990e809542916065fbb29e4ec4d", "gitDir": "test/corpus/repos/javascript", - "sha2": "5e8b10bc0227ed241ed8ab30e5a15a183707edd6" + "sha2": "fee3454c33f7cd5eab32dc5aa7e9735a955ace4f" } ,{ "testCaseDescription": "javascript-import-replacement-insert-test", @@ -162,7 +154,6 @@ 1, 1 ], - "filepath": "import.js", "end": [ 1, 38 @@ -179,7 +170,6 @@ 2, 1 ], - "filepath": "import.js", "end": [ 2, 37 @@ -196,7 +186,6 @@ 3, 1 ], - "filepath": "import.js", "end": [ 3, 34 @@ -213,7 +202,6 @@ 4, 1 ], - "filepath": "import.js", "end": [ 4, 50 @@ -230,7 +218,6 @@ 5, 1 ], - "filepath": "import.js", "end": [ 5, 66 @@ -247,7 +234,6 @@ 6, 1 ], - "filepath": "import.js", "end": [ 6, 78 @@ -264,7 +250,6 @@ 7, 1 ], - "filepath": "import.js", "end": [ 7, 50 @@ -281,7 +266,6 @@ 8, 1 ], - "filepath": "import.js", "end": [ 8, 19 @@ -298,7 +282,6 @@ 9, 1 ], - "filepath": "import.js", "end": [ 9, 33 @@ -315,7 +298,6 @@ 10, 1 ], - "filepath": "import.js", "end": [ 10, 34 @@ -332,7 +314,6 @@ 11, 1 ], - "filepath": "import.js", "end": [ 11, 30 @@ -349,7 +330,6 @@ 12, 1 ], - "filepath": "import.js", "end": [ 12, 46 @@ -366,7 +346,6 @@ 13, 1 ], - "filepath": "import.js", "end": [ 13, 57 @@ -383,7 +362,6 @@ 14, 1 ], - "filepath": "import.js", "end": [ 14, 70 @@ -400,7 +378,6 @@ 15, 1 ], - "filepath": "import.js", "end": [ 15, 50 @@ -417,7 +394,6 @@ 16, 1 ], - "filepath": "import.js", "end": [ 16, 22 @@ -434,9 +410,9 @@ "filePaths": [ "import.js" ], - "sha1": "5e8b10bc0227ed241ed8ab30e5a15a183707edd6", + "sha1": "fee3454c33f7cd5eab32dc5aa7e9735a955ace4f", "gitDir": "test/corpus/repos/javascript", - "sha2": "faa56959b912ba2a79d43c329d9934720e4d282c" + "sha2": "c28f080d1c93051935cf781db3adc4d790fdd8ed" } ,{ "testCaseDescription": "javascript-import-delete-insert-test", @@ -451,7 +427,6 @@ 1, 27 ], - "filepath": "import.js", "end": [ 1, 37 @@ -462,7 +437,6 @@ 1, 27 ], - "filepath": "import.js", "end": [ 1, 32 @@ -481,7 +455,6 @@ 2, 28 ], - "filepath": "import.js", "end": [ 2, 36 @@ -492,7 +465,6 @@ 2, 23 ], - "filepath": "import.js", "end": [ 2, 33 @@ -511,7 +483,6 @@ 2, 13 ], - "filepath": "import.js", "end": [ 2, 22 @@ -522,7 +493,6 @@ 2, 13 ], - "filepath": "import.js", "end": [ 2, 17 @@ -541,7 +511,6 @@ 3, 25 ], - "filepath": "import.js", "end": [ 3, 33 @@ -552,7 +521,6 @@ 3, 24 ], - "filepath": "import.js", "end": [ 3, 29 @@ -571,7 +539,6 @@ 3, 10 ], - "filepath": "import.js", "end": [ 3, 17 @@ -582,7 +549,6 @@ 3, 10 ], - "filepath": "import.js", "end": [ 3, 16 @@ -601,7 +567,6 @@ 4, 37 ], - "filepath": "import.js", "end": [ 4, 49 @@ -612,7 +577,6 @@ 4, 35 ], - "filepath": "import.js", "end": [ 4, 45 @@ -631,7 +595,6 @@ 4, 10 ], - "filepath": "import.js", "end": [ 4, 18 @@ -642,7 +605,6 @@ 4, 10 ], - "filepath": "import.js", "end": [ 4, 17 @@ -661,7 +623,6 @@ 4, 21 ], - "filepath": "import.js", "end": [ 4, 29 @@ -672,7 +633,6 @@ 4, 20 ], - "filepath": "import.js", "end": [ 4, 27 @@ -691,7 +651,6 @@ 5, 54 ], - "filepath": "import.js", "end": [ 5, 65 @@ -702,7 +661,6 @@ 5, 45 ], - "filepath": "import.js", "end": [ 5, 56 @@ -721,7 +679,6 @@ 5, 10 ], - "filepath": "import.js", "end": [ 5, 18 @@ -732,7 +689,6 @@ 5, 10 ], - "filepath": "import.js", "end": [ 5, 17 @@ -751,7 +707,6 @@ 5, 21 ], - "filepath": "import.js", "end": [ 5, 29 @@ -762,7 +717,6 @@ 5, 20 ], - "filepath": "import.js", "end": [ 5, 27 @@ -781,7 +735,6 @@ 5, 33 ], - "filepath": "import.js", "end": [ 5, 46 @@ -792,7 +745,6 @@ 5, 31 ], - "filepath": "import.js", "end": [ 5, 37 @@ -811,7 +763,6 @@ 6, 68 ], - "filepath": "import.js", "end": [ 6, 77 @@ -822,7 +773,6 @@ 6, 59 ], - "filepath": "import.js", "end": [ 6, 69 @@ -841,7 +791,6 @@ 6, 25 ], - "filepath": "import.js", "end": [ 6, 33 @@ -852,7 +801,6 @@ 6, 25 ], - "filepath": "import.js", "end": [ 6, 32 @@ -871,7 +819,6 @@ 6, 35 ], - "filepath": "import.js", "end": [ 6, 43 @@ -882,7 +829,6 @@ 6, 34 ], - "filepath": "import.js", "end": [ 6, 41 @@ -901,7 +847,6 @@ 6, 47 ], - "filepath": "import.js", "end": [ 6, 60 @@ -912,7 +857,6 @@ 6, 45 ], - "filepath": "import.js", "end": [ 6, 51 @@ -931,7 +875,6 @@ 7, 41 ], - "filepath": "import.js", "end": [ 7, 49 @@ -942,7 +885,6 @@ 7, 38 ], - "filepath": "import.js", "end": [ 7, 49 @@ -961,7 +903,6 @@ 7, 28 ], - "filepath": "import.js", "end": [ 7, 35 @@ -972,7 +913,6 @@ 7, 28 ], - "filepath": "import.js", "end": [ 7, 32 @@ -991,7 +931,6 @@ 8, 8 ], - "filepath": "import.js", "end": [ 8, 18 @@ -1002,7 +941,6 @@ 8, 8 ], - "filepath": "import.js", "end": [ 8, 21 @@ -1020,9 +958,9 @@ "filePaths": [ "import.js" ], - "sha1": "faa56959b912ba2a79d43c329d9934720e4d282c", + "sha1": "c28f080d1c93051935cf781db3adc4d790fdd8ed", "gitDir": "test/corpus/repos/javascript", - "sha2": "caa4826fd6304b8c918cc23708255da3318468e2" + "sha2": "26fd9db0c145d7d502593173826c0f1ad31dc8d6" } ,{ "testCaseDescription": "javascript-import-replacement-test", @@ -1037,7 +975,6 @@ 1, 27 ], - "filepath": "import.js", "end": [ 1, 32 @@ -1048,7 +985,6 @@ 1, 27 ], - "filepath": "import.js", "end": [ 1, 37 @@ -1067,7 +1003,6 @@ 2, 23 ], - "filepath": "import.js", "end": [ 2, 33 @@ -1078,7 +1013,6 @@ 2, 28 ], - "filepath": "import.js", "end": [ 2, 36 @@ -1097,7 +1031,6 @@ 2, 13 ], - "filepath": "import.js", "end": [ 2, 17 @@ -1108,7 +1041,6 @@ 2, 13 ], - "filepath": "import.js", "end": [ 2, 22 @@ -1127,7 +1059,6 @@ 3, 24 ], - "filepath": "import.js", "end": [ 3, 29 @@ -1138,7 +1069,6 @@ 3, 25 ], - "filepath": "import.js", "end": [ 3, 33 @@ -1157,7 +1087,6 @@ 3, 10 ], - "filepath": "import.js", "end": [ 3, 16 @@ -1168,7 +1097,6 @@ 3, 10 ], - "filepath": "import.js", "end": [ 3, 17 @@ -1187,7 +1115,6 @@ 4, 35 ], - "filepath": "import.js", "end": [ 4, 45 @@ -1198,7 +1125,6 @@ 4, 37 ], - "filepath": "import.js", "end": [ 4, 49 @@ -1217,7 +1143,6 @@ 4, 10 ], - "filepath": "import.js", "end": [ 4, 17 @@ -1228,7 +1153,6 @@ 4, 10 ], - "filepath": "import.js", "end": [ 4, 18 @@ -1247,7 +1171,6 @@ 4, 20 ], - "filepath": "import.js", "end": [ 4, 27 @@ -1258,7 +1181,6 @@ 4, 21 ], - "filepath": "import.js", "end": [ 4, 29 @@ -1277,7 +1199,6 @@ 5, 45 ], - "filepath": "import.js", "end": [ 5, 56 @@ -1288,7 +1209,6 @@ 5, 54 ], - "filepath": "import.js", "end": [ 5, 65 @@ -1307,7 +1227,6 @@ 5, 10 ], - "filepath": "import.js", "end": [ 5, 17 @@ -1318,7 +1237,6 @@ 5, 10 ], - "filepath": "import.js", "end": [ 5, 18 @@ -1337,7 +1255,6 @@ 5, 20 ], - "filepath": "import.js", "end": [ 5, 27 @@ -1348,7 +1265,6 @@ 5, 21 ], - "filepath": "import.js", "end": [ 5, 29 @@ -1367,7 +1283,6 @@ 5, 31 ], - "filepath": "import.js", "end": [ 5, 37 @@ -1378,7 +1293,6 @@ 5, 33 ], - "filepath": "import.js", "end": [ 5, 46 @@ -1397,7 +1311,6 @@ 6, 59 ], - "filepath": "import.js", "end": [ 6, 69 @@ -1408,7 +1321,6 @@ 6, 68 ], - "filepath": "import.js", "end": [ 6, 77 @@ -1427,7 +1339,6 @@ 6, 25 ], - "filepath": "import.js", "end": [ 6, 32 @@ -1438,7 +1349,6 @@ 6, 25 ], - "filepath": "import.js", "end": [ 6, 33 @@ -1457,7 +1367,6 @@ 6, 34 ], - "filepath": "import.js", "end": [ 6, 41 @@ -1468,7 +1377,6 @@ 6, 35 ], - "filepath": "import.js", "end": [ 6, 43 @@ -1487,7 +1395,6 @@ 6, 45 ], - "filepath": "import.js", "end": [ 6, 51 @@ -1498,7 +1405,6 @@ 6, 47 ], - "filepath": "import.js", "end": [ 6, 60 @@ -1517,7 +1423,6 @@ 7, 38 ], - "filepath": "import.js", "end": [ 7, 49 @@ -1528,7 +1433,6 @@ 7, 41 ], - "filepath": "import.js", "end": [ 7, 49 @@ -1547,7 +1451,6 @@ 7, 28 ], - "filepath": "import.js", "end": [ 7, 32 @@ -1558,7 +1461,6 @@ 7, 28 ], - "filepath": "import.js", "end": [ 7, 35 @@ -1577,7 +1479,6 @@ 8, 8 ], - "filepath": "import.js", "end": [ 8, 21 @@ -1588,7 +1489,6 @@ 8, 8 ], - "filepath": "import.js", "end": [ 8, 18 @@ -1606,9 +1506,9 @@ "filePaths": [ "import.js" ], - "sha1": "caa4826fd6304b8c918cc23708255da3318468e2", + "sha1": "26fd9db0c145d7d502593173826c0f1ad31dc8d6", "gitDir": "test/corpus/repos/javascript", - "sha2": "db616e2f957db4d05d9a710268e9d8bf826b7b99" + "sha2": "4847728b759c2df8061704204aeb1b24c3d9e5f4" } ,{ "testCaseDescription": "javascript-import-delete-replacement-test", @@ -1622,7 +1522,6 @@ 1, 1 ], - "filepath": "import.js", "end": [ 1, 38 @@ -1639,7 +1538,6 @@ 2, 1 ], - "filepath": "import.js", "end": [ 2, 37 @@ -1656,7 +1554,6 @@ 3, 1 ], - "filepath": "import.js", "end": [ 3, 34 @@ -1673,7 +1570,6 @@ 4, 1 ], - "filepath": "import.js", "end": [ 4, 50 @@ -1690,7 +1586,6 @@ 5, 1 ], - "filepath": "import.js", "end": [ 5, 66 @@ -1707,7 +1602,6 @@ 6, 1 ], - "filepath": "import.js", "end": [ 6, 78 @@ -1724,7 +1618,6 @@ 7, 1 ], - "filepath": "import.js", "end": [ 7, 50 @@ -1741,7 +1634,6 @@ 8, 1 ], - "filepath": "import.js", "end": [ 8, 19 @@ -1758,7 +1650,6 @@ 9, 1 ], - "filepath": "import.js", "end": [ 9, 33 @@ -1775,7 +1666,6 @@ 10, 1 ], - "filepath": "import.js", "end": [ 10, 34 @@ -1792,7 +1682,6 @@ 11, 1 ], - "filepath": "import.js", "end": [ 11, 30 @@ -1809,7 +1698,6 @@ 12, 1 ], - "filepath": "import.js", "end": [ 12, 46 @@ -1826,7 +1714,6 @@ 13, 1 ], - "filepath": "import.js", "end": [ 13, 57 @@ -1843,7 +1730,6 @@ 14, 1 ], - "filepath": "import.js", "end": [ 14, 70 @@ -1860,7 +1746,6 @@ 15, 1 ], - "filepath": "import.js", "end": [ 15, 50 @@ -1877,7 +1762,6 @@ 16, 1 ], - "filepath": "import.js", "end": [ 16, 22 @@ -1894,7 +1778,6 @@ 9, 1 ], - "filepath": "import.js", "end": [ 9, 38 @@ -1911,7 +1794,6 @@ 10, 1 ], - "filepath": "import.js", "end": [ 10, 37 @@ -1928,7 +1810,6 @@ 11, 1 ], - "filepath": "import.js", "end": [ 11, 34 @@ -1945,7 +1826,6 @@ 12, 1 ], - "filepath": "import.js", "end": [ 12, 50 @@ -1962,7 +1842,6 @@ 13, 1 ], - "filepath": "import.js", "end": [ 13, 66 @@ -1979,7 +1858,6 @@ 14, 1 ], - "filepath": "import.js", "end": [ 14, 78 @@ -1996,7 +1874,6 @@ 15, 1 ], - "filepath": "import.js", "end": [ 15, 50 @@ -2013,7 +1890,6 @@ 16, 1 ], - "filepath": "import.js", "end": [ 16, 19 @@ -2030,9 +1906,9 @@ "filePaths": [ "import.js" ], - "sha1": "db616e2f957db4d05d9a710268e9d8bf826b7b99", + "sha1": "4847728b759c2df8061704204aeb1b24c3d9e5f4", "gitDir": "test/corpus/repos/javascript", - "sha2": "bf70d2b51a4872cd42ebd2b274ca80cb002041d0" + "sha2": "c4905d598dec191b7fd2b15c8d4345ffd7077818" } ,{ "testCaseDescription": "javascript-import-delete-test", @@ -2046,7 +1922,6 @@ 1, 1 ], - "filepath": "import.js", "end": [ 1, 33 @@ -2063,7 +1938,6 @@ 2, 1 ], - "filepath": "import.js", "end": [ 2, 34 @@ -2080,7 +1954,6 @@ 3, 1 ], - "filepath": "import.js", "end": [ 3, 30 @@ -2097,7 +1970,6 @@ 4, 1 ], - "filepath": "import.js", "end": [ 4, 46 @@ -2114,7 +1986,6 @@ 5, 1 ], - "filepath": "import.js", "end": [ 5, 57 @@ -2131,7 +2002,6 @@ 6, 1 ], - "filepath": "import.js", "end": [ 6, 70 @@ -2148,7 +2018,6 @@ 7, 1 ], - "filepath": "import.js", "end": [ 7, 50 @@ -2165,7 +2034,6 @@ 8, 1 ], - "filepath": "import.js", "end": [ 8, 22 @@ -2182,9 +2050,9 @@ "filePaths": [ "import.js" ], - "sha1": "bf70d2b51a4872cd42ebd2b274ca80cb002041d0", + "sha1": "c4905d598dec191b7fd2b15c8d4345ffd7077818", "gitDir": "test/corpus/repos/javascript", - "sha2": "07c7bdcbe8b8df8ca4b6a73abb42e8180e7c99b1" + "sha2": "2aefc12e72888e28a1b4fbc7129a1446eb798bc9" } ,{ "testCaseDescription": "javascript-import-delete-rest-test", @@ -2198,7 +2066,6 @@ 1, 1 ], - "filepath": "import.js", "end": [ 1, 38 @@ -2215,7 +2082,6 @@ 2, 1 ], - "filepath": "import.js", "end": [ 2, 37 @@ -2232,7 +2098,6 @@ 3, 1 ], - "filepath": "import.js", "end": [ 3, 34 @@ -2249,7 +2114,6 @@ 4, 1 ], - "filepath": "import.js", "end": [ 4, 50 @@ -2266,7 +2130,6 @@ 5, 1 ], - "filepath": "import.js", "end": [ 5, 66 @@ -2283,7 +2146,6 @@ 6, 1 ], - "filepath": "import.js", "end": [ 6, 78 @@ -2300,7 +2162,6 @@ 7, 1 ], - "filepath": "import.js", "end": [ 7, 50 @@ -2317,7 +2178,6 @@ 8, 1 ], - "filepath": "import.js", "end": [ 8, 19 @@ -2334,7 +2194,7 @@ "filePaths": [ "import.js" ], - "sha1": "07c7bdcbe8b8df8ca4b6a73abb42e8180e7c99b1", + "sha1": "2aefc12e72888e28a1b4fbc7129a1446eb798bc9", "gitDir": "test/corpus/repos/javascript", - "sha2": "a38a53d0bc89ceb5a135e55a161b8f18004b3a09" + "sha2": "baeaa709caa4158226fe70b8121ab16a18b17da7" }] diff --git a/test/corpus/diff-summaries/javascript/math-assignment-operator.json b/test/corpus/diff-summaries/javascript/math-assignment-operator.json index 8dacfd99a..46b2e1a24 100644 --- a/test/corpus/diff-summaries/javascript/math-assignment-operator.json +++ b/test/corpus/diff-summaries/javascript/math-assignment-operator.json @@ -10,7 +10,6 @@ 1, 1 ], - "filepath": "math-assignment-operator.js", "end": [ 1, 7 @@ -27,9 +26,9 @@ "filePaths": [ "math-assignment-operator.js" ], - "sha1": "f0aa5967e70024ba3cff3ab45027fc5cc4ee095e", + "sha1": "2ca5d30b5fd1ebde9a1a664d1b82909706d83564", "gitDir": "test/corpus/repos/javascript", - "sha2": "e51af0f932ca8d3e2ed4b6747caf2686c3b5d59a" + "sha2": "c77665677c2dd3b83ba7fefcc63b1d827ffdcce8" } ,{ "testCaseDescription": "javascript-math-assignment-operator-replacement-insert-test", @@ -43,7 +42,6 @@ 1, 1 ], - "filepath": "math-assignment-operator.js", "end": [ 1, 7 @@ -60,7 +58,6 @@ 2, 1 ], - "filepath": "math-assignment-operator.js", "end": [ 2, 7 @@ -77,9 +74,9 @@ "filePaths": [ "math-assignment-operator.js" ], - "sha1": "e51af0f932ca8d3e2ed4b6747caf2686c3b5d59a", + "sha1": "c77665677c2dd3b83ba7fefcc63b1d827ffdcce8", "gitDir": "test/corpus/repos/javascript", - "sha2": "c275a6337b41c09d9af3e45dac32866166d6d108" + "sha2": "c2ba4903792d6930abf7ebb660bed06435c39849" } ,{ "testCaseDescription": "javascript-math-assignment-operator-delete-insert-test", @@ -94,7 +91,6 @@ 1, 6 ], - "filepath": "math-assignment-operator.js", "end": [ 1, 7 @@ -105,7 +101,6 @@ 1, 6 ], - "filepath": "math-assignment-operator.js", "end": [ 1, 7 @@ -123,9 +118,9 @@ "filePaths": [ "math-assignment-operator.js" ], - "sha1": "c275a6337b41c09d9af3e45dac32866166d6d108", + "sha1": "c2ba4903792d6930abf7ebb660bed06435c39849", "gitDir": "test/corpus/repos/javascript", - "sha2": "133dec934bc2d22a5a1229203d2210eea53610d8" + "sha2": "c96c70294daa06c57e6f14cb42372b346066a52e" } ,{ "testCaseDescription": "javascript-math-assignment-operator-replacement-test", @@ -140,7 +135,6 @@ 1, 6 ], - "filepath": "math-assignment-operator.js", "end": [ 1, 7 @@ -151,7 +145,6 @@ 1, 6 ], - "filepath": "math-assignment-operator.js", "end": [ 1, 7 @@ -169,9 +162,9 @@ "filePaths": [ "math-assignment-operator.js" ], - "sha1": "133dec934bc2d22a5a1229203d2210eea53610d8", + "sha1": "c96c70294daa06c57e6f14cb42372b346066a52e", "gitDir": "test/corpus/repos/javascript", - "sha2": "5cd9a21ff71c7010a6d906ea09fd31b02271e031" + "sha2": "4d6fe1c4cb15bf7b1801b95862c70203b5134321" } ,{ "testCaseDescription": "javascript-math-assignment-operator-delete-replacement-test", @@ -185,7 +178,6 @@ 1, 1 ], - "filepath": "math-assignment-operator.js", "end": [ 1, 7 @@ -202,7 +194,6 @@ 2, 1 ], - "filepath": "math-assignment-operator.js", "end": [ 2, 7 @@ -219,7 +210,6 @@ 2, 1 ], - "filepath": "math-assignment-operator.js", "end": [ 2, 7 @@ -236,9 +226,9 @@ "filePaths": [ "math-assignment-operator.js" ], - "sha1": "5cd9a21ff71c7010a6d906ea09fd31b02271e031", + "sha1": "4d6fe1c4cb15bf7b1801b95862c70203b5134321", "gitDir": "test/corpus/repos/javascript", - "sha2": "56aac6220eebc2056db47d65b36ecffdf221842b" + "sha2": "7ac20dbefc8263eb02d522920b8ddb59fdd0b6f3" } ,{ "testCaseDescription": "javascript-math-assignment-operator-delete-test", @@ -252,7 +242,6 @@ 1, 1 ], - "filepath": "math-assignment-operator.js", "end": [ 1, 7 @@ -269,9 +258,9 @@ "filePaths": [ "math-assignment-operator.js" ], - "sha1": "56aac6220eebc2056db47d65b36ecffdf221842b", + "sha1": "7ac20dbefc8263eb02d522920b8ddb59fdd0b6f3", "gitDir": "test/corpus/repos/javascript", - "sha2": "b2e8c33b4a78911afe8658fde43534f2edacaaac" + "sha2": "8a2ae9688bfc32aab39c26627746cc570e7b65f1" } ,{ "testCaseDescription": "javascript-math-assignment-operator-delete-rest-test", @@ -285,7 +274,6 @@ 1, 1 ], - "filepath": "math-assignment-operator.js", "end": [ 1, 7 @@ -302,7 +290,7 @@ "filePaths": [ "math-assignment-operator.js" ], - "sha1": "b2e8c33b4a78911afe8658fde43534f2edacaaac", + "sha1": "8a2ae9688bfc32aab39c26627746cc570e7b65f1", "gitDir": "test/corpus/repos/javascript", - "sha2": "2ed03a05e45eb7ba8974047b60a101f32957a87e" + "sha2": "4c3640ed0b5a448eb803d90898cfa643a6dd4b71" }] diff --git a/test/corpus/diff-summaries/javascript/math-operator.json b/test/corpus/diff-summaries/javascript/math-operator.json index 71eff2d69..dc0743394 100644 --- a/test/corpus/diff-summaries/javascript/math-operator.json +++ b/test/corpus/diff-summaries/javascript/math-operator.json @@ -10,7 +10,6 @@ 1, 1 ], - "filepath": "math-operator.js", "end": [ 1, 18 @@ -27,9 +26,9 @@ "filePaths": [ "math-operator.js" ], - "sha1": "2583ff8eb54838a4bae616ec1c051ebfc0c6b21c", + "sha1": "c8a29a317ded4687f422bf074dfc78c3780f2ded", "gitDir": "test/corpus/repos/javascript", - "sha2": "64a4ce3ce9b3fa2c5eb7f1262197328f488bed3b" + "sha2": "135b3432e0d4822c6691f908127689ddaf48bd21" } ,{ "testCaseDescription": "javascript-math-operator-replacement-insert-test", @@ -43,7 +42,6 @@ 1, 1 ], - "filepath": "math-operator.js", "end": [ 1, 18 @@ -60,7 +58,6 @@ 2, 1 ], - "filepath": "math-operator.js", "end": [ 2, 18 @@ -77,9 +74,9 @@ "filePaths": [ "math-operator.js" ], - "sha1": "64a4ce3ce9b3fa2c5eb7f1262197328f488bed3b", + "sha1": "135b3432e0d4822c6691f908127689ddaf48bd21", "gitDir": "test/corpus/repos/javascript", - "sha2": "f4374903c814a2fb2c715e9dd3f61bc86a39373a" + "sha2": "3bef0fdd5c4f40c4a5842980e32ea9c294e7c1a6" } ,{ "testCaseDescription": "javascript-math-operator-delete-insert-test", @@ -94,7 +91,6 @@ 1, 9 ], - "filepath": "math-operator.js", "end": [ 1, 10 @@ -105,7 +101,6 @@ 1, 9 ], - "filepath": "math-operator.js", "end": [ 1, 10 @@ -124,7 +119,6 @@ 1, 17 ], - "filepath": "math-operator.js", "end": [ 1, 18 @@ -135,7 +129,6 @@ 1, 17 ], - "filepath": "math-operator.js", "end": [ 1, 18 @@ -153,9 +146,9 @@ "filePaths": [ "math-operator.js" ], - "sha1": "f4374903c814a2fb2c715e9dd3f61bc86a39373a", + "sha1": "3bef0fdd5c4f40c4a5842980e32ea9c294e7c1a6", "gitDir": "test/corpus/repos/javascript", - "sha2": "abcb678e0cde4b601c58cc5d02a312833ccae59c" + "sha2": "2a1f800e6611e6552c0cc03a075a948be66d821b" } ,{ "testCaseDescription": "javascript-math-operator-replacement-test", @@ -170,7 +163,6 @@ 1, 9 ], - "filepath": "math-operator.js", "end": [ 1, 10 @@ -181,7 +173,6 @@ 1, 9 ], - "filepath": "math-operator.js", "end": [ 1, 10 @@ -200,7 +191,6 @@ 1, 17 ], - "filepath": "math-operator.js", "end": [ 1, 18 @@ -211,7 +201,6 @@ 1, 17 ], - "filepath": "math-operator.js", "end": [ 1, 18 @@ -229,9 +218,9 @@ "filePaths": [ "math-operator.js" ], - "sha1": "abcb678e0cde4b601c58cc5d02a312833ccae59c", + "sha1": "2a1f800e6611e6552c0cc03a075a948be66d821b", "gitDir": "test/corpus/repos/javascript", - "sha2": "b2f3e1b498736c5ccf5978bd038257f754486853" + "sha2": "83d548b2ea37b6ff82a5d4934403fcb33b62de2b" } ,{ "testCaseDescription": "javascript-math-operator-delete-replacement-test", @@ -245,7 +234,6 @@ 1, 1 ], - "filepath": "math-operator.js", "end": [ 1, 18 @@ -262,7 +250,6 @@ 2, 1 ], - "filepath": "math-operator.js", "end": [ 2, 18 @@ -279,7 +266,6 @@ 2, 1 ], - "filepath": "math-operator.js", "end": [ 2, 18 @@ -296,9 +282,9 @@ "filePaths": [ "math-operator.js" ], - "sha1": "b2f3e1b498736c5ccf5978bd038257f754486853", + "sha1": "83d548b2ea37b6ff82a5d4934403fcb33b62de2b", "gitDir": "test/corpus/repos/javascript", - "sha2": "25f392b16a9459b195c5f08a4a3417f10c42ee43" + "sha2": "ccc69e5cabb4346d9e6e78a680419433965bcaff" } ,{ "testCaseDescription": "javascript-math-operator-delete-test", @@ -312,7 +298,6 @@ 1, 1 ], - "filepath": "math-operator.js", "end": [ 1, 18 @@ -329,9 +314,9 @@ "filePaths": [ "math-operator.js" ], - "sha1": "25f392b16a9459b195c5f08a4a3417f10c42ee43", + "sha1": "ccc69e5cabb4346d9e6e78a680419433965bcaff", "gitDir": "test/corpus/repos/javascript", - "sha2": "7dc3ffdbdbc87605365fab5e4604971e2d35f66c" + "sha2": "e12a6e350ec50729b2c8392702dea68bc4f25e19" } ,{ "testCaseDescription": "javascript-math-operator-delete-rest-test", @@ -345,7 +330,6 @@ 1, 1 ], - "filepath": "math-operator.js", "end": [ 1, 18 @@ -362,7 +346,7 @@ "filePaths": [ "math-operator.js" ], - "sha1": "7dc3ffdbdbc87605365fab5e4604971e2d35f66c", + "sha1": "e12a6e350ec50729b2c8392702dea68bc4f25e19", "gitDir": "test/corpus/repos/javascript", - "sha2": "5e5d08f5cc6ce83a5663d10215511b13bddd76e3" + "sha2": "a93c385a37621e58b24c3192ac242f152296869b" }] diff --git a/test/corpus/diff-summaries/javascript/member-access-assignment.json b/test/corpus/diff-summaries/javascript/member-access-assignment.json index bd63fb05f..0f5f56a26 100644 --- a/test/corpus/diff-summaries/javascript/member-access-assignment.json +++ b/test/corpus/diff-summaries/javascript/member-access-assignment.json @@ -10,7 +10,6 @@ 1, 1 ], - "filepath": "member-access-assignment.js", "end": [ 1, 8 @@ -27,9 +26,9 @@ "filePaths": [ "member-access-assignment.js" ], - "sha1": "515ac3ce664c0458a2daec58a009a959898bebfc", + "sha1": "fe1724a351896c9096078d5bc7dfa8e89539cddb", "gitDir": "test/corpus/repos/javascript", - "sha2": "5b13b077ccde1b06ff25f19444c018d023966ff3" + "sha2": "ac71d5f2e73babcd37c24cb8fade58d08652beae" } ,{ "testCaseDescription": "javascript-member-access-assignment-replacement-insert-test", @@ -43,7 +42,6 @@ 1, 1 ], - "filepath": "member-access-assignment.js", "end": [ 1, 8 @@ -60,7 +58,6 @@ 2, 1 ], - "filepath": "member-access-assignment.js", "end": [ 2, 8 @@ -77,9 +74,9 @@ "filePaths": [ "member-access-assignment.js" ], - "sha1": "5b13b077ccde1b06ff25f19444c018d023966ff3", + "sha1": "ac71d5f2e73babcd37c24cb8fade58d08652beae", "gitDir": "test/corpus/repos/javascript", - "sha2": "81b23ec877edcbdda611f11f84bb5fc2bbcdff99" + "sha2": "45817a82720c40b2e12c4e53e11e3a405e840783" } ,{ "testCaseDescription": "javascript-member-access-assignment-delete-insert-test", @@ -94,7 +91,6 @@ 1, 7 ], - "filepath": "member-access-assignment.js", "end": [ 1, 8 @@ -105,7 +101,6 @@ 1, 7 ], - "filepath": "member-access-assignment.js", "end": [ 1, 8 @@ -123,9 +118,9 @@ "filePaths": [ "member-access-assignment.js" ], - "sha1": "81b23ec877edcbdda611f11f84bb5fc2bbcdff99", + "sha1": "45817a82720c40b2e12c4e53e11e3a405e840783", "gitDir": "test/corpus/repos/javascript", - "sha2": "371c940952fcefebd1b7004ccc085c1779e4ce5e" + "sha2": "0b254a3f1120d1cee678a827d0bf5bfb6b57156b" } ,{ "testCaseDescription": "javascript-member-access-assignment-replacement-test", @@ -140,7 +135,6 @@ 1, 7 ], - "filepath": "member-access-assignment.js", "end": [ 1, 8 @@ -151,7 +145,6 @@ 1, 7 ], - "filepath": "member-access-assignment.js", "end": [ 1, 8 @@ -169,9 +162,9 @@ "filePaths": [ "member-access-assignment.js" ], - "sha1": "371c940952fcefebd1b7004ccc085c1779e4ce5e", + "sha1": "0b254a3f1120d1cee678a827d0bf5bfb6b57156b", "gitDir": "test/corpus/repos/javascript", - "sha2": "31906f7f34ded701fe34854abc03d472ba2df3b9" + "sha2": "24e43482adbbe8bdbb56191bc3b2ac1387049f77" } ,{ "testCaseDescription": "javascript-member-access-assignment-delete-replacement-test", @@ -185,7 +178,6 @@ 1, 1 ], - "filepath": "member-access-assignment.js", "end": [ 1, 8 @@ -202,7 +194,6 @@ 2, 1 ], - "filepath": "member-access-assignment.js", "end": [ 2, 8 @@ -219,7 +210,6 @@ 2, 1 ], - "filepath": "member-access-assignment.js", "end": [ 2, 8 @@ -236,9 +226,9 @@ "filePaths": [ "member-access-assignment.js" ], - "sha1": "31906f7f34ded701fe34854abc03d472ba2df3b9", + "sha1": "24e43482adbbe8bdbb56191bc3b2ac1387049f77", "gitDir": "test/corpus/repos/javascript", - "sha2": "4121aac1f6341d50d31dd3711e233dd1256a835b" + "sha2": "ec5bc8a34cb2ac731d35de1a1ef2a41f479d9085" } ,{ "testCaseDescription": "javascript-member-access-assignment-delete-test", @@ -252,7 +242,6 @@ 1, 1 ], - "filepath": "member-access-assignment.js", "end": [ 1, 8 @@ -269,9 +258,9 @@ "filePaths": [ "member-access-assignment.js" ], - "sha1": "4121aac1f6341d50d31dd3711e233dd1256a835b", + "sha1": "ec5bc8a34cb2ac731d35de1a1ef2a41f479d9085", "gitDir": "test/corpus/repos/javascript", - "sha2": "d0d284d66e3a6432df3c60db9a4d3fdad41fa8fd" + "sha2": "17c753388d910dee728182ae1a1f3ad9fdce2616" } ,{ "testCaseDescription": "javascript-member-access-assignment-delete-rest-test", @@ -285,7 +274,6 @@ 1, 1 ], - "filepath": "member-access-assignment.js", "end": [ 1, 8 @@ -302,7 +290,7 @@ "filePaths": [ "member-access-assignment.js" ], - "sha1": "d0d284d66e3a6432df3c60db9a4d3fdad41fa8fd", + "sha1": "17c753388d910dee728182ae1a1f3ad9fdce2616", "gitDir": "test/corpus/repos/javascript", - "sha2": "24df96dbbf63c7c9940c4c18cd4286ca25dae952" + "sha2": "43c155e0e1c235f4a7a66d19b55ec670aa456167" }] diff --git a/test/corpus/diff-summaries/javascript/member-access.json b/test/corpus/diff-summaries/javascript/member-access.json index 50024bdc5..2b1e45650 100644 --- a/test/corpus/diff-summaries/javascript/member-access.json +++ b/test/corpus/diff-summaries/javascript/member-access.json @@ -10,7 +10,6 @@ 1, 1 ], - "filepath": "member-access.js", "end": [ 1, 15 @@ -27,9 +26,9 @@ "filePaths": [ "member-access.js" ], - "sha1": "8b63530b6848d8ef3e2e5b0cb37c9d6372fdac1b", + "sha1": "34dda706308957a43236571644aff6e35d5ed5c8", "gitDir": "test/corpus/repos/javascript", - "sha2": "67254a51988c3fc555ea2ad08cb5da975dea54c7" + "sha2": "229478a3867e3a976746a8e8e30e79ed9383d47b" } ,{ "testCaseDescription": "javascript-member-access-replacement-insert-test", @@ -43,7 +42,6 @@ 1, 1 ], - "filepath": "member-access.js", "end": [ 1, 20 @@ -60,7 +58,6 @@ 2, 1 ], - "filepath": "member-access.js", "end": [ 2, 15 @@ -77,9 +74,9 @@ "filePaths": [ "member-access.js" ], - "sha1": "67254a51988c3fc555ea2ad08cb5da975dea54c7", + "sha1": "229478a3867e3a976746a8e8e30e79ed9383d47b", "gitDir": "test/corpus/repos/javascript", - "sha2": "9f605846402d4b84e66d7de139128aff21fd4152" + "sha2": "77a6c524dc810aef2a026ada74ae51db6401d399" } ,{ "testCaseDescription": "javascript-member-access-delete-insert-test", @@ -94,7 +91,6 @@ 1, 3 ], - "filepath": "member-access.js", "end": [ 1, 20 @@ -105,7 +101,6 @@ 1, 3 ], - "filepath": "member-access.js", "end": [ 1, 15 @@ -123,9 +118,9 @@ "filePaths": [ "member-access.js" ], - "sha1": "9f605846402d4b84e66d7de139128aff21fd4152", + "sha1": "77a6c524dc810aef2a026ada74ae51db6401d399", "gitDir": "test/corpus/repos/javascript", - "sha2": "688af6aeeff6c78f97b665ca7298eeabe92e5dfa" + "sha2": "a24d2c73c061cc1124a76c8d53d324f6d8d56b1b" } ,{ "testCaseDescription": "javascript-member-access-replacement-test", @@ -140,7 +135,6 @@ 1, 3 ], - "filepath": "member-access.js", "end": [ 1, 15 @@ -151,7 +145,6 @@ 1, 3 ], - "filepath": "member-access.js", "end": [ 1, 20 @@ -169,9 +162,9 @@ "filePaths": [ "member-access.js" ], - "sha1": "688af6aeeff6c78f97b665ca7298eeabe92e5dfa", + "sha1": "a24d2c73c061cc1124a76c8d53d324f6d8d56b1b", "gitDir": "test/corpus/repos/javascript", - "sha2": "e85146e179caf3262c97df585a1bf6bd328b2f80" + "sha2": "397d55476cc1b66ae98e4f258055a0a5a6860f4c" } ,{ "testCaseDescription": "javascript-member-access-delete-replacement-test", @@ -185,7 +178,6 @@ 1, 1 ], - "filepath": "member-access.js", "end": [ 1, 20 @@ -202,7 +194,6 @@ 2, 1 ], - "filepath": "member-access.js", "end": [ 2, 15 @@ -219,7 +210,6 @@ 2, 1 ], - "filepath": "member-access.js", "end": [ 2, 20 @@ -236,9 +226,9 @@ "filePaths": [ "member-access.js" ], - "sha1": "e85146e179caf3262c97df585a1bf6bd328b2f80", + "sha1": "397d55476cc1b66ae98e4f258055a0a5a6860f4c", "gitDir": "test/corpus/repos/javascript", - "sha2": "91679d6168bd44ae5e1ef72b3f60c0fc8eab8fb8" + "sha2": "5677ae58e398c0c1918513007208da0fdf21e181" } ,{ "testCaseDescription": "javascript-member-access-delete-test", @@ -252,7 +242,6 @@ 1, 1 ], - "filepath": "member-access.js", "end": [ 1, 15 @@ -269,9 +258,9 @@ "filePaths": [ "member-access.js" ], - "sha1": "91679d6168bd44ae5e1ef72b3f60c0fc8eab8fb8", + "sha1": "5677ae58e398c0c1918513007208da0fdf21e181", "gitDir": "test/corpus/repos/javascript", - "sha2": "7dccbf4bf9d388652848c2083833dec41e90728c" + "sha2": "9b5bb8a95ace1c7bf6b2017bacaaf538c41508b5" } ,{ "testCaseDescription": "javascript-member-access-delete-rest-test", @@ -285,7 +274,6 @@ 1, 1 ], - "filepath": "member-access.js", "end": [ 1, 20 @@ -302,7 +290,7 @@ "filePaths": [ "member-access.js" ], - "sha1": "7dccbf4bf9d388652848c2083833dec41e90728c", + "sha1": "9b5bb8a95ace1c7bf6b2017bacaaf538c41508b5", "gitDir": "test/corpus/repos/javascript", - "sha2": "559c6157818131001576dffc43aefab616ea53e2" + "sha2": "13bf09743306aea0c956273f7ead3bc1759bcee5" }] diff --git a/test/corpus/diff-summaries/javascript/method-call.json b/test/corpus/diff-summaries/javascript/method-call.json index 8c7352729..db69e239e 100644 --- a/test/corpus/diff-summaries/javascript/method-call.json +++ b/test/corpus/diff-summaries/javascript/method-call.json @@ -10,7 +10,6 @@ 1, 1 ], - "filepath": "method-call.js", "end": [ 1, 32 @@ -27,9 +26,9 @@ "filePaths": [ "method-call.js" ], - "sha1": "d1d52518c72665ed2a4fee18636ce01a6be5ad1b", + "sha1": "bd15264892a7cee21de72ea983762c38c1f900b7", "gitDir": "test/corpus/repos/javascript", - "sha2": "782a58af563009deefa90e0955f95e312254dd79" + "sha2": "3cc7d50b45588156ba2ffcfa2d5af9ad12a00b9b" } ,{ "testCaseDescription": "javascript-method-call-replacement-insert-test", @@ -43,7 +42,6 @@ 1, 1 ], - "filepath": "method-call.js", "end": [ 1, 32 @@ -60,7 +58,6 @@ 2, 1 ], - "filepath": "method-call.js", "end": [ 2, 32 @@ -77,9 +74,9 @@ "filePaths": [ "method-call.js" ], - "sha1": "782a58af563009deefa90e0955f95e312254dd79", + "sha1": "3cc7d50b45588156ba2ffcfa2d5af9ad12a00b9b", "gitDir": "test/corpus/repos/javascript", - "sha2": "b218990554430ee36a78605df7a541292f0b68ca" + "sha2": "6475c883d4ed36ef6f15fa3e3a12ff893f728264" } ,{ "testCaseDescription": "javascript-method-call-delete-insert-test", @@ -94,7 +91,6 @@ 1, 25 ], - "filepath": "method-call.js", "end": [ 1, 31 @@ -105,7 +101,6 @@ 1, 25 ], - "filepath": "method-call.js", "end": [ 1, 31 @@ -123,9 +118,9 @@ "filePaths": [ "method-call.js" ], - "sha1": "b218990554430ee36a78605df7a541292f0b68ca", + "sha1": "6475c883d4ed36ef6f15fa3e3a12ff893f728264", "gitDir": "test/corpus/repos/javascript", - "sha2": "c784724d66e515a67ca8b0a1ed63dd3b31ab2a57" + "sha2": "efc3bb8710951cd60a0535ffc790eb411415c39f" } ,{ "testCaseDescription": "javascript-method-call-replacement-test", @@ -140,7 +135,6 @@ 1, 25 ], - "filepath": "method-call.js", "end": [ 1, 31 @@ -151,7 +145,6 @@ 1, 25 ], - "filepath": "method-call.js", "end": [ 1, 31 @@ -169,9 +162,9 @@ "filePaths": [ "method-call.js" ], - "sha1": "c784724d66e515a67ca8b0a1ed63dd3b31ab2a57", + "sha1": "efc3bb8710951cd60a0535ffc790eb411415c39f", "gitDir": "test/corpus/repos/javascript", - "sha2": "92e526265448c695d1a2b435bdb1e47b712d6b8a" + "sha2": "92f66e257a70c7c4cfe02a2b740c995018679430" } ,{ "testCaseDescription": "javascript-method-call-delete-replacement-test", @@ -185,7 +178,6 @@ 1, 1 ], - "filepath": "method-call.js", "end": [ 1, 32 @@ -202,7 +194,6 @@ 2, 1 ], - "filepath": "method-call.js", "end": [ 2, 32 @@ -219,7 +210,6 @@ 2, 1 ], - "filepath": "method-call.js", "end": [ 2, 32 @@ -236,9 +226,9 @@ "filePaths": [ "method-call.js" ], - "sha1": "92e526265448c695d1a2b435bdb1e47b712d6b8a", + "sha1": "92f66e257a70c7c4cfe02a2b740c995018679430", "gitDir": "test/corpus/repos/javascript", - "sha2": "578212d963bc0a379d767d9b9c995582efb0774f" + "sha2": "be9128442aa9fe04e0d8adf7d386c09b65c0dc68" } ,{ "testCaseDescription": "javascript-method-call-delete-test", @@ -252,7 +242,6 @@ 1, 1 ], - "filepath": "method-call.js", "end": [ 1, 32 @@ -269,9 +258,9 @@ "filePaths": [ "method-call.js" ], - "sha1": "578212d963bc0a379d767d9b9c995582efb0774f", + "sha1": "be9128442aa9fe04e0d8adf7d386c09b65c0dc68", "gitDir": "test/corpus/repos/javascript", - "sha2": "b2ed03c62a18b28a033b883f8496c5cf89c0eb4b" + "sha2": "2d65956f15bf31fbf63e5c67b1b1d9c23a233b5a" } ,{ "testCaseDescription": "javascript-method-call-delete-rest-test", @@ -285,7 +274,6 @@ 1, 1 ], - "filepath": "method-call.js", "end": [ 1, 32 @@ -302,7 +290,7 @@ "filePaths": [ "method-call.js" ], - "sha1": "b2ed03c62a18b28a033b883f8496c5cf89c0eb4b", + "sha1": "2d65956f15bf31fbf63e5c67b1b1d9c23a233b5a", "gitDir": "test/corpus/repos/javascript", - "sha2": "ba35b41bf9e5b77b55af13c5001569dc5ce4ae9b" + "sha2": "e1bef609317c32e852d5067ed84baeea51868e53" }] diff --git a/test/corpus/diff-summaries/javascript/named-function.json b/test/corpus/diff-summaries/javascript/named-function.json index f5a948404..b220803ca 100644 --- a/test/corpus/diff-summaries/javascript/named-function.json +++ b/test/corpus/diff-summaries/javascript/named-function.json @@ -10,7 +10,6 @@ 1, 1 ], - "filepath": "named-function.js", "end": [ 1, 42 @@ -27,9 +26,9 @@ "filePaths": [ "named-function.js" ], - "sha1": "4f10daadd1f0292f7909951043926535151b0c5d", + "sha1": "9e9c5e08a862128a46c888405ef29a584da0e923", "gitDir": "test/corpus/repos/javascript", - "sha2": "f19ad72631f7bff25fda760b486a1dc7820b7b77" + "sha2": "f31cd7b33a288a75aa8d5b0d3488c0de723cb5dd" } ,{ "testCaseDescription": "javascript-named-function-replacement-insert-test", @@ -43,7 +42,6 @@ 1, 1 ], - "filepath": "named-function.js", "end": [ 1, 45 @@ -60,7 +58,6 @@ 2, 1 ], - "filepath": "named-function.js", "end": [ 2, 42 @@ -77,9 +74,9 @@ "filePaths": [ "named-function.js" ], - "sha1": "f19ad72631f7bff25fda760b486a1dc7820b7b77", + "sha1": "f31cd7b33a288a75aa8d5b0d3488c0de723cb5dd", "gitDir": "test/corpus/repos/javascript", - "sha2": "eb28c552425afa7b5830c5358de72056ed48c090" + "sha2": "a4e9ee32075f16e11f34bef7a33851a493f688ee" } ,{ "testCaseDescription": "javascript-named-function-delete-insert-test", @@ -94,7 +91,6 @@ 1, 10 ], - "filepath": "named-function.js", "end": [ 1, 25 @@ -105,7 +101,6 @@ 1, 10 ], - "filepath": "named-function.js", "end": [ 1, 20 @@ -123,7 +118,6 @@ 1, 21 ], - "filepath": "named-function.js", "end": [ 1, 25 @@ -140,7 +134,6 @@ 1, 27 ], - "filepath": "named-function.js", "end": [ 1, 31 @@ -157,7 +150,6 @@ 1, 35 ], - "filepath": "named-function.js", "end": [ 1, 39 @@ -174,7 +166,6 @@ 1, 30 ], - "filepath": "named-function.js", "end": [ 1, 43 @@ -191,9 +182,9 @@ "filePaths": [ "named-function.js" ], - "sha1": "eb28c552425afa7b5830c5358de72056ed48c090", + "sha1": "a4e9ee32075f16e11f34bef7a33851a493f688ee", "gitDir": "test/corpus/repos/javascript", - "sha2": "08011f3d6953e93599cb6242aa603cc3f2245824" + "sha2": "4de27cb3698e46c8c941c58e677cfe3d8ab48078" } ,{ "testCaseDescription": "javascript-named-function-replacement-test", @@ -208,7 +199,6 @@ 1, 10 ], - "filepath": "named-function.js", "end": [ 1, 20 @@ -219,7 +209,6 @@ 1, 10 ], - "filepath": "named-function.js", "end": [ 1, 25 @@ -237,7 +226,6 @@ 1, 21 ], - "filepath": "named-function.js", "end": [ 1, 25 @@ -254,7 +242,6 @@ 1, 27 ], - "filepath": "named-function.js", "end": [ 1, 31 @@ -271,7 +258,6 @@ 1, 30 ], - "filepath": "named-function.js", "end": [ 1, 43 @@ -288,7 +274,6 @@ 1, 35 ], - "filepath": "named-function.js", "end": [ 1, 39 @@ -305,9 +290,9 @@ "filePaths": [ "named-function.js" ], - "sha1": "08011f3d6953e93599cb6242aa603cc3f2245824", + "sha1": "4de27cb3698e46c8c941c58e677cfe3d8ab48078", "gitDir": "test/corpus/repos/javascript", - "sha2": "ebed4cdaaa3d19dd0012db680fe261e0006c5c2a" + "sha2": "c947b40e91668836ccb2dcb0aa705ae25b5c9509" } ,{ "testCaseDescription": "javascript-named-function-delete-replacement-test", @@ -321,7 +306,6 @@ 1, 1 ], - "filepath": "named-function.js", "end": [ 1, 45 @@ -338,7 +322,6 @@ 2, 1 ], - "filepath": "named-function.js", "end": [ 2, 42 @@ -355,7 +338,6 @@ 2, 1 ], - "filepath": "named-function.js", "end": [ 2, 45 @@ -372,9 +354,9 @@ "filePaths": [ "named-function.js" ], - "sha1": "ebed4cdaaa3d19dd0012db680fe261e0006c5c2a", + "sha1": "c947b40e91668836ccb2dcb0aa705ae25b5c9509", "gitDir": "test/corpus/repos/javascript", - "sha2": "cd4d6840a6128e3ae540047e6a709d5d0b0a5c47" + "sha2": "2e880b7e68923075fc2c7c8b61534af7afa3ea44" } ,{ "testCaseDescription": "javascript-named-function-delete-test", @@ -388,7 +370,6 @@ 1, 1 ], - "filepath": "named-function.js", "end": [ 1, 42 @@ -405,9 +386,9 @@ "filePaths": [ "named-function.js" ], - "sha1": "cd4d6840a6128e3ae540047e6a709d5d0b0a5c47", + "sha1": "2e880b7e68923075fc2c7c8b61534af7afa3ea44", "gitDir": "test/corpus/repos/javascript", - "sha2": "f766ee585573125a533e1bd46f74f83cae95793c" + "sha2": "a298f3ad3bab2182e5d50a6908514d6ad210d5a9" } ,{ "testCaseDescription": "javascript-named-function-delete-rest-test", @@ -421,7 +402,6 @@ 1, 1 ], - "filepath": "named-function.js", "end": [ 1, 45 @@ -438,7 +418,7 @@ "filePaths": [ "named-function.js" ], - "sha1": "f766ee585573125a533e1bd46f74f83cae95793c", + "sha1": "a298f3ad3bab2182e5d50a6908514d6ad210d5a9", "gitDir": "test/corpus/repos/javascript", - "sha2": "8b63530b6848d8ef3e2e5b0cb37c9d6372fdac1b" + "sha2": "00345376742839aaf8cdbefbe8cb10795489044a" }] diff --git a/test/corpus/diff-summaries/javascript/nested-do-while-in-function.json b/test/corpus/diff-summaries/javascript/nested-do-while-in-function.json index a94c35c15..c43d91fd1 100644 --- a/test/corpus/diff-summaries/javascript/nested-do-while-in-function.json +++ b/test/corpus/diff-summaries/javascript/nested-do-while-in-function.json @@ -10,7 +10,6 @@ 1, 1 ], - "filepath": "export.js", "end": [ 1, 39 @@ -27,7 +26,6 @@ 2, 1 ], - "filepath": "export.js", "end": [ 2, 58 @@ -44,7 +42,6 @@ 3, 1 ], - "filepath": "export.js", "end": [ 3, 32 @@ -61,7 +58,6 @@ 4, 1 ], - "filepath": "export.js", "end": [ 4, 57 @@ -78,7 +74,6 @@ 5, 1 ], - "filepath": "export.js", "end": [ 5, 30 @@ -95,7 +90,6 @@ 6, 1 ], - "filepath": "export.js", "end": [ 6, 32 @@ -112,7 +106,6 @@ 7, 1 ], - "filepath": "export.js", "end": [ 7, 37 @@ -129,7 +122,6 @@ 8, 1 ], - "filepath": "export.js", "end": [ 8, 29 @@ -146,7 +138,6 @@ 9, 1 ], - "filepath": "export.js", "end": [ 9, 21 @@ -163,7 +154,6 @@ 10, 1 ], - "filepath": "export.js", "end": [ 10, 43 @@ -180,7 +170,6 @@ 11, 1 ], - "filepath": "export.js", "end": [ 11, 65 @@ -197,9 +186,9 @@ "filePaths": [ "export.js" ], - "sha1": "a5cbd53d1d80069c2a2569cb7b54e87a94157893", + "sha1": "cf784ad9d8d9843aa79915afc98e7c8c7def3bce", "gitDir": "test/corpus/repos/javascript", - "sha2": "aa70a259619bb125f7fa05c185e0a23dc41e818a" + "sha2": "6a61c15ee9b892ad6fb99edf5ed4fddaaf1668cd" } ,{ "testCaseDescription": "javascript-export-replacement-insert-test", @@ -213,7 +202,6 @@ 1, 1 ], - "filepath": "export.js", "end": [ 1, 39 @@ -230,7 +218,6 @@ 2, 1 ], - "filepath": "export.js", "end": [ 2, 58 @@ -247,7 +234,6 @@ 3, 1 ], - "filepath": "export.js", "end": [ 3, 32 @@ -264,7 +250,6 @@ 4, 1 ], - "filepath": "export.js", "end": [ 4, 57 @@ -281,7 +266,6 @@ 5, 1 ], - "filepath": "export.js", "end": [ 5, 35 @@ -298,7 +282,6 @@ 6, 1 ], - "filepath": "export.js", "end": [ 6, 39 @@ -315,7 +298,6 @@ 7, 1 ], - "filepath": "export.js", "end": [ 7, 31 @@ -332,7 +314,6 @@ 8, 1 ], - "filepath": "export.js", "end": [ 8, 31 @@ -349,7 +330,6 @@ 9, 1 ], - "filepath": "export.js", "end": [ 9, 21 @@ -366,7 +346,6 @@ 10, 1 ], - "filepath": "export.js", "end": [ 10, 44 @@ -383,7 +362,6 @@ 11, 1 ], - "filepath": "export.js", "end": [ 11, 66 @@ -400,7 +378,6 @@ 12, 1 ], - "filepath": "export.js", "end": [ 12, 39 @@ -417,7 +394,6 @@ 13, 1 ], - "filepath": "export.js", "end": [ 13, 58 @@ -434,7 +410,6 @@ 14, 1 ], - "filepath": "export.js", "end": [ 14, 32 @@ -451,7 +426,6 @@ 15, 1 ], - "filepath": "export.js", "end": [ 15, 57 @@ -468,7 +442,6 @@ 16, 1 ], - "filepath": "export.js", "end": [ 16, 30 @@ -485,7 +458,6 @@ 17, 1 ], - "filepath": "export.js", "end": [ 17, 32 @@ -502,7 +474,6 @@ 18, 1 ], - "filepath": "export.js", "end": [ 18, 37 @@ -519,7 +490,6 @@ 19, 1 ], - "filepath": "export.js", "end": [ 19, 29 @@ -536,7 +506,6 @@ 20, 1 ], - "filepath": "export.js", "end": [ 20, 21 @@ -553,7 +522,6 @@ 21, 1 ], - "filepath": "export.js", "end": [ 21, 43 @@ -570,7 +538,6 @@ 22, 1 ], - "filepath": "export.js", "end": [ 22, 65 @@ -587,9 +554,9 @@ "filePaths": [ "export.js" ], - "sha1": "aa70a259619bb125f7fa05c185e0a23dc41e818a", + "sha1": "6a61c15ee9b892ad6fb99edf5ed4fddaaf1668cd", "gitDir": "test/corpus/repos/javascript", - "sha2": "8080542e661c8c62e1c0830f485e297b5187a8c2" + "sha2": "8b44c437b4f4230802f75d171dfe1e45a5131045" } ,{ "testCaseDescription": "javascript-export-delete-insert-test", @@ -604,7 +571,6 @@ 1, 10 ], - "filepath": "export.js", "end": [ 1, 15 @@ -615,7 +581,6 @@ 1, 10 ], - "filepath": "export.js", "end": [ 1, 15 @@ -634,7 +599,6 @@ 1, 17 ], - "filepath": "export.js", "end": [ 1, 22 @@ -645,7 +609,6 @@ 1, 17 ], - "filepath": "export.js", "end": [ 1, 22 @@ -664,7 +627,6 @@ 1, 24 ], - "filepath": "export.js", "end": [ 1, 29 @@ -675,7 +637,6 @@ 1, 24 ], - "filepath": "export.js", "end": [ 1, 29 @@ -694,7 +655,6 @@ 1, 31 ], - "filepath": "export.js", "end": [ 1, 36 @@ -705,7 +665,6 @@ 1, 31 ], - "filepath": "export.js", "end": [ 1, 36 @@ -724,7 +683,6 @@ 2, 10 ], - "filepath": "export.js", "end": [ 2, 19 @@ -735,7 +693,6 @@ 2, 10 ], - "filepath": "export.js", "end": [ 2, 19 @@ -754,7 +711,6 @@ 2, 23 ], - "filepath": "export.js", "end": [ 2, 28 @@ -765,7 +721,6 @@ 2, 23 ], - "filepath": "export.js", "end": [ 2, 28 @@ -784,7 +739,6 @@ 2, 30 ], - "filepath": "export.js", "end": [ 2, 39 @@ -795,7 +749,6 @@ 2, 30 ], - "filepath": "export.js", "end": [ 2, 39 @@ -814,7 +767,6 @@ 2, 43 ], - "filepath": "export.js", "end": [ 2, 48 @@ -825,7 +777,6 @@ 2, 43 ], - "filepath": "export.js", "end": [ 2, 48 @@ -844,7 +795,6 @@ 2, 50 ], - "filepath": "export.js", "end": [ 2, 55 @@ -855,7 +805,6 @@ 2, 50 ], - "filepath": "export.js", "end": [ 2, 55 @@ -874,7 +823,6 @@ 3, 12 ], - "filepath": "export.js", "end": [ 3, 17 @@ -885,7 +833,6 @@ 3, 12 ], - "filepath": "export.js", "end": [ 3, 17 @@ -904,7 +851,6 @@ 3, 19 ], - "filepath": "export.js", "end": [ 3, 24 @@ -915,7 +861,6 @@ 3, 19 ], - "filepath": "export.js", "end": [ 3, 24 @@ -934,7 +879,6 @@ 3, 26 ], - "filepath": "export.js", "end": [ 3, 31 @@ -945,7 +889,6 @@ 3, 26 ], - "filepath": "export.js", "end": [ 3, 31 @@ -964,7 +907,6 @@ 4, 12 ], - "filepath": "export.js", "end": [ 4, 17 @@ -975,7 +917,6 @@ 4, 12 ], - "filepath": "export.js", "end": [ 4, 17 @@ -994,7 +935,6 @@ 4, 20 ], - "filepath": "export.js", "end": [ 4, 26 @@ -1005,7 +945,6 @@ 4, 20 ], - "filepath": "export.js", "end": [ 4, 26 @@ -1024,7 +963,6 @@ 4, 28 ], - "filepath": "export.js", "end": [ 4, 33 @@ -1035,7 +973,6 @@ 4, 28 ], - "filepath": "export.js", "end": [ 4, 33 @@ -1054,7 +991,6 @@ 4, 36 ], - "filepath": "export.js", "end": [ 4, 42 @@ -1065,7 +1001,6 @@ 4, 36 ], - "filepath": "export.js", "end": [ 4, 42 @@ -1084,7 +1019,6 @@ 4, 44 ], - "filepath": "export.js", "end": [ 4, 49 @@ -1095,7 +1029,6 @@ 4, 44 ], - "filepath": "export.js", "end": [ 4, 49 @@ -1114,7 +1047,6 @@ 4, 51 ], - "filepath": "export.js", "end": [ 4, 56 @@ -1125,7 +1057,6 @@ 4, 51 ], - "filepath": "export.js", "end": [ 4, 56 @@ -1144,7 +1075,6 @@ 5, 16 ], - "filepath": "export.js", "end": [ 5, 34 @@ -1155,7 +1085,6 @@ 5, 16 ], - "filepath": "export.js", "end": [ 5, 29 @@ -1173,7 +1102,6 @@ 6, 1 ], - "filepath": "export.js", "end": [ 6, 32 @@ -1190,7 +1118,6 @@ 7, 1 ], - "filepath": "export.js", "end": [ 7, 37 @@ -1207,7 +1134,6 @@ 8, 1 ], - "filepath": "export.js", "end": [ 8, 29 @@ -1224,7 +1150,6 @@ 9, 1 ], - "filepath": "export.js", "end": [ 9, 21 @@ -1241,7 +1166,6 @@ 10, 1 ], - "filepath": "export.js", "end": [ 10, 43 @@ -1258,7 +1182,6 @@ 11, 1 ], - "filepath": "export.js", "end": [ 11, 65 @@ -1275,7 +1198,6 @@ 6, 1 ], - "filepath": "export.js", "end": [ 6, 39 @@ -1292,7 +1214,6 @@ 7, 1 ], - "filepath": "export.js", "end": [ 7, 31 @@ -1309,7 +1230,6 @@ 8, 1 ], - "filepath": "export.js", "end": [ 8, 31 @@ -1326,7 +1246,6 @@ 9, 1 ], - "filepath": "export.js", "end": [ 9, 21 @@ -1343,7 +1262,6 @@ 10, 1 ], - "filepath": "export.js", "end": [ 10, 44 @@ -1360,7 +1278,6 @@ 11, 1 ], - "filepath": "export.js", "end": [ 11, 66 @@ -1377,9 +1294,9 @@ "filePaths": [ "export.js" ], - "sha1": "8080542e661c8c62e1c0830f485e297b5187a8c2", + "sha1": "8b44c437b4f4230802f75d171dfe1e45a5131045", "gitDir": "test/corpus/repos/javascript", - "sha2": "677b8c31a22bf2ae4a664a71efcc3ab08aa2ff99" + "sha2": "a785e114db03c32878ca52d5eb63919ab6a2157e" } ,{ "testCaseDescription": "javascript-export-replacement-test", @@ -1394,7 +1311,6 @@ 1, 10 ], - "filepath": "export.js", "end": [ 1, 15 @@ -1405,7 +1321,6 @@ 1, 10 ], - "filepath": "export.js", "end": [ 1, 15 @@ -1424,7 +1339,6 @@ 1, 17 ], - "filepath": "export.js", "end": [ 1, 22 @@ -1435,7 +1349,6 @@ 1, 17 ], - "filepath": "export.js", "end": [ 1, 22 @@ -1454,7 +1367,6 @@ 1, 24 ], - "filepath": "export.js", "end": [ 1, 29 @@ -1465,7 +1377,6 @@ 1, 24 ], - "filepath": "export.js", "end": [ 1, 29 @@ -1484,7 +1395,6 @@ 1, 31 ], - "filepath": "export.js", "end": [ 1, 36 @@ -1495,7 +1405,6 @@ 1, 31 ], - "filepath": "export.js", "end": [ 1, 36 @@ -1513,7 +1422,6 @@ 2, 1 ], - "filepath": "export.js", "end": [ 2, 58 @@ -1530,7 +1438,6 @@ 3, 1 ], - "filepath": "export.js", "end": [ 3, 32 @@ -1547,7 +1454,6 @@ 4, 1 ], - "filepath": "export.js", "end": [ 4, 57 @@ -1564,7 +1470,6 @@ 5, 1 ], - "filepath": "export.js", "end": [ 5, 35 @@ -1581,7 +1486,6 @@ 6, 1 ], - "filepath": "export.js", "end": [ 6, 39 @@ -1598,7 +1502,6 @@ 7, 1 ], - "filepath": "export.js", "end": [ 7, 31 @@ -1615,7 +1518,6 @@ 8, 1 ], - "filepath": "export.js", "end": [ 8, 31 @@ -1632,7 +1534,6 @@ 9, 1 ], - "filepath": "export.js", "end": [ 9, 21 @@ -1649,7 +1550,6 @@ 10, 1 ], - "filepath": "export.js", "end": [ 10, 44 @@ -1666,7 +1566,6 @@ 11, 1 ], - "filepath": "export.js", "end": [ 11, 66 @@ -1683,7 +1582,6 @@ 2, 1 ], - "filepath": "export.js", "end": [ 2, 58 @@ -1700,7 +1598,6 @@ 3, 1 ], - "filepath": "export.js", "end": [ 3, 32 @@ -1717,7 +1614,6 @@ 4, 1 ], - "filepath": "export.js", "end": [ 4, 57 @@ -1734,7 +1630,6 @@ 5, 1 ], - "filepath": "export.js", "end": [ 5, 30 @@ -1751,7 +1646,6 @@ 6, 1 ], - "filepath": "export.js", "end": [ 6, 32 @@ -1768,7 +1662,6 @@ 7, 1 ], - "filepath": "export.js", "end": [ 7, 37 @@ -1785,7 +1678,6 @@ 8, 1 ], - "filepath": "export.js", "end": [ 8, 29 @@ -1802,7 +1694,6 @@ 9, 1 ], - "filepath": "export.js", "end": [ 9, 21 @@ -1819,7 +1710,6 @@ 10, 1 ], - "filepath": "export.js", "end": [ 10, 43 @@ -1836,7 +1726,6 @@ 11, 1 ], - "filepath": "export.js", "end": [ 11, 65 @@ -1853,9 +1742,9 @@ "filePaths": [ "export.js" ], - "sha1": "677b8c31a22bf2ae4a664a71efcc3ab08aa2ff99", + "sha1": "a785e114db03c32878ca52d5eb63919ab6a2157e", "gitDir": "test/corpus/repos/javascript", - "sha2": "3323a81331df2355890b6c599ded7fda43137561" + "sha2": "630f93e2ef51a3dbf92c5d9070fb2c8d4e77cbe0" } ,{ "testCaseDescription": "javascript-export-delete-replacement-test", @@ -1869,7 +1758,6 @@ 1, 1 ], - "filepath": "export.js", "end": [ 1, 39 @@ -1886,7 +1774,6 @@ 2, 1 ], - "filepath": "export.js", "end": [ 2, 58 @@ -1903,7 +1790,6 @@ 3, 1 ], - "filepath": "export.js", "end": [ 3, 32 @@ -1920,7 +1806,6 @@ 4, 1 ], - "filepath": "export.js", "end": [ 4, 57 @@ -1937,7 +1822,6 @@ 5, 1 ], - "filepath": "export.js", "end": [ 5, 35 @@ -1954,7 +1838,6 @@ 6, 1 ], - "filepath": "export.js", "end": [ 6, 39 @@ -1971,7 +1854,6 @@ 7, 1 ], - "filepath": "export.js", "end": [ 7, 31 @@ -1988,7 +1870,6 @@ 8, 1 ], - "filepath": "export.js", "end": [ 8, 31 @@ -2005,7 +1886,6 @@ 9, 1 ], - "filepath": "export.js", "end": [ 9, 21 @@ -2022,7 +1902,6 @@ 10, 1 ], - "filepath": "export.js", "end": [ 10, 44 @@ -2039,7 +1918,6 @@ 11, 1 ], - "filepath": "export.js", "end": [ 11, 66 @@ -2056,7 +1934,6 @@ 12, 1 ], - "filepath": "export.js", "end": [ 12, 39 @@ -2073,7 +1950,6 @@ 13, 1 ], - "filepath": "export.js", "end": [ 13, 58 @@ -2090,7 +1966,6 @@ 14, 1 ], - "filepath": "export.js", "end": [ 14, 32 @@ -2107,7 +1982,6 @@ 15, 1 ], - "filepath": "export.js", "end": [ 15, 57 @@ -2124,7 +1998,6 @@ 16, 1 ], - "filepath": "export.js", "end": [ 16, 30 @@ -2141,7 +2014,6 @@ 17, 1 ], - "filepath": "export.js", "end": [ 17, 32 @@ -2158,7 +2030,6 @@ 18, 1 ], - "filepath": "export.js", "end": [ 18, 37 @@ -2175,7 +2046,6 @@ 19, 1 ], - "filepath": "export.js", "end": [ 19, 29 @@ -2192,7 +2062,6 @@ 20, 1 ], - "filepath": "export.js", "end": [ 20, 21 @@ -2209,7 +2078,6 @@ 21, 1 ], - "filepath": "export.js", "end": [ 21, 43 @@ -2226,7 +2094,6 @@ 22, 1 ], - "filepath": "export.js", "end": [ 22, 65 @@ -2243,7 +2110,6 @@ 12, 1 ], - "filepath": "export.js", "end": [ 12, 39 @@ -2260,7 +2126,6 @@ 13, 1 ], - "filepath": "export.js", "end": [ 13, 58 @@ -2277,7 +2142,6 @@ 14, 1 ], - "filepath": "export.js", "end": [ 14, 32 @@ -2294,7 +2158,6 @@ 15, 1 ], - "filepath": "export.js", "end": [ 15, 57 @@ -2311,7 +2174,6 @@ 16, 1 ], - "filepath": "export.js", "end": [ 16, 35 @@ -2328,7 +2190,6 @@ 17, 1 ], - "filepath": "export.js", "end": [ 17, 39 @@ -2345,7 +2206,6 @@ 18, 1 ], - "filepath": "export.js", "end": [ 18, 31 @@ -2362,7 +2222,6 @@ 19, 1 ], - "filepath": "export.js", "end": [ 19, 31 @@ -2379,7 +2238,6 @@ 20, 1 ], - "filepath": "export.js", "end": [ 20, 21 @@ -2396,7 +2254,6 @@ 21, 1 ], - "filepath": "export.js", "end": [ 21, 44 @@ -2413,7 +2270,6 @@ 22, 1 ], - "filepath": "export.js", "end": [ 22, 66 @@ -2430,9 +2286,9 @@ "filePaths": [ "export.js" ], - "sha1": "3323a81331df2355890b6c599ded7fda43137561", + "sha1": "630f93e2ef51a3dbf92c5d9070fb2c8d4e77cbe0", "gitDir": "test/corpus/repos/javascript", - "sha2": "2cab123e6ec7bbca286ced8d7f2d151d33f0b0db" + "sha2": "4dc68416478b18e5ab4d0cb03d1be06129ffde31" } ,{ "testCaseDescription": "javascript-export-delete-test", @@ -2446,7 +2302,6 @@ 1, 1 ], - "filepath": "export.js", "end": [ 1, 39 @@ -2463,7 +2318,6 @@ 2, 1 ], - "filepath": "export.js", "end": [ 2, 58 @@ -2480,7 +2334,6 @@ 3, 1 ], - "filepath": "export.js", "end": [ 3, 32 @@ -2497,7 +2350,6 @@ 4, 1 ], - "filepath": "export.js", "end": [ 4, 57 @@ -2514,7 +2366,6 @@ 5, 1 ], - "filepath": "export.js", "end": [ 5, 30 @@ -2531,7 +2382,6 @@ 6, 1 ], - "filepath": "export.js", "end": [ 6, 32 @@ -2548,7 +2398,6 @@ 7, 1 ], - "filepath": "export.js", "end": [ 7, 37 @@ -2565,7 +2414,6 @@ 8, 1 ], - "filepath": "export.js", "end": [ 8, 29 @@ -2582,7 +2430,6 @@ 9, 1 ], - "filepath": "export.js", "end": [ 9, 21 @@ -2599,7 +2446,6 @@ 10, 1 ], - "filepath": "export.js", "end": [ 10, 43 @@ -2616,7 +2462,6 @@ 11, 1 ], - "filepath": "export.js", "end": [ 11, 65 @@ -2633,9 +2478,9 @@ "filePaths": [ "export.js" ], - "sha1": "2cab123e6ec7bbca286ced8d7f2d151d33f0b0db", + "sha1": "4dc68416478b18e5ab4d0cb03d1be06129ffde31", "gitDir": "test/corpus/repos/javascript", - "sha2": "aa415fd98f8f0fb76a5e2f26d115b348e5f27e35" + "sha2": "11d28b7ee48f99ad7e371a3ff7a3afcb482ecac5" } ,{ "testCaseDescription": "javascript-export-delete-rest-test", @@ -2649,7 +2494,6 @@ 1, 1 ], - "filepath": "export.js", "end": [ 1, 39 @@ -2666,7 +2510,6 @@ 2, 1 ], - "filepath": "export.js", "end": [ 2, 58 @@ -2683,7 +2526,6 @@ 3, 1 ], - "filepath": "export.js", "end": [ 3, 32 @@ -2700,7 +2542,6 @@ 4, 1 ], - "filepath": "export.js", "end": [ 4, 57 @@ -2717,7 +2558,6 @@ 5, 1 ], - "filepath": "export.js", "end": [ 5, 35 @@ -2734,7 +2574,6 @@ 6, 1 ], - "filepath": "export.js", "end": [ 6, 39 @@ -2751,7 +2590,6 @@ 7, 1 ], - "filepath": "export.js", "end": [ 7, 31 @@ -2768,7 +2606,6 @@ 8, 1 ], - "filepath": "export.js", "end": [ 8, 31 @@ -2785,7 +2622,6 @@ 9, 1 ], - "filepath": "export.js", "end": [ 9, 21 @@ -2802,7 +2638,6 @@ 10, 1 ], - "filepath": "export.js", "end": [ 10, 44 @@ -2819,7 +2654,6 @@ 11, 1 ], - "filepath": "export.js", "end": [ 11, 66 @@ -2836,7 +2670,7 @@ "filePaths": [ "export.js" ], - "sha1": "aa415fd98f8f0fb76a5e2f26d115b348e5f27e35", + "sha1": "11d28b7ee48f99ad7e371a3ff7a3afcb482ecac5", "gitDir": "test/corpus/repos/javascript", - "sha2": "725a0ee6c4535512f82e53d65edf151cc8f724eb" + "sha2": "a1ec5326a248592c7deb7a7e3b3ece00b97506bb" }] diff --git a/test/corpus/diff-summaries/javascript/nested-functions.json b/test/corpus/diff-summaries/javascript/nested-functions.json index 1c59add7f..dbe14a466 100644 --- a/test/corpus/diff-summaries/javascript/nested-functions.json +++ b/test/corpus/diff-summaries/javascript/nested-functions.json @@ -10,7 +10,6 @@ 1, 1 ], - "filepath": "nested-functions.js", "end": [ 1, 103 @@ -27,9 +26,9 @@ "filePaths": [ "nested-functions.js" ], - "sha1": "aa8be129d06030fa7cb344ba9e16f5ad9eff8e47", + "sha1": "d0057ff388e8070743e2f2922cff0d9b3a2ad5de", "gitDir": "test/corpus/repos/javascript", - "sha2": "f07812ff3c1415768f6a45b0cb12483fd96b81af" + "sha2": "4ac6b2869a5665de7edc7342598666e37dd1a139" } ,{ "testCaseDescription": "javascript-nested-functions-replacement-insert-test", @@ -43,7 +42,6 @@ 1, 1 ], - "filepath": "nested-functions.js", "end": [ 1, 103 @@ -60,7 +58,6 @@ 2, 1 ], - "filepath": "nested-functions.js", "end": [ 2, 103 @@ -77,9 +74,9 @@ "filePaths": [ "nested-functions.js" ], - "sha1": "f07812ff3c1415768f6a45b0cb12483fd96b81af", + "sha1": "4ac6b2869a5665de7edc7342598666e37dd1a139", "gitDir": "test/corpus/repos/javascript", - "sha2": "663e4b64a04136d3a85d2b1095313feae62b8ee2" + "sha2": "394a62ade20d4d86615aec875b6e77b67c610af0" } ,{ "testCaseDescription": "javascript-nested-functions-delete-insert-test", @@ -94,7 +91,6 @@ 1, 74 ], - "filepath": "nested-functions.js", "end": [ 1, 78 @@ -105,7 +101,6 @@ 1, 74 ], - "filepath": "nested-functions.js", "end": [ 1, 78 @@ -124,7 +119,6 @@ 1, 93 ], - "filepath": "nested-functions.js", "end": [ 1, 97 @@ -135,7 +129,6 @@ 1, 93 ], - "filepath": "nested-functions.js", "end": [ 1, 97 @@ -153,9 +146,9 @@ "filePaths": [ "nested-functions.js" ], - "sha1": "663e4b64a04136d3a85d2b1095313feae62b8ee2", + "sha1": "394a62ade20d4d86615aec875b6e77b67c610af0", "gitDir": "test/corpus/repos/javascript", - "sha2": "5264f63751b2830a3156bc9466b96b327c28268c" + "sha2": "7904f2aa3a357840ae49cbeb09842f4483d5b928" } ,{ "testCaseDescription": "javascript-nested-functions-replacement-test", @@ -170,7 +163,6 @@ 1, 74 ], - "filepath": "nested-functions.js", "end": [ 1, 78 @@ -181,7 +173,6 @@ 1, 74 ], - "filepath": "nested-functions.js", "end": [ 1, 78 @@ -200,7 +191,6 @@ 1, 93 ], - "filepath": "nested-functions.js", "end": [ 1, 97 @@ -211,7 +201,6 @@ 1, 93 ], - "filepath": "nested-functions.js", "end": [ 1, 97 @@ -229,9 +218,9 @@ "filePaths": [ "nested-functions.js" ], - "sha1": "5264f63751b2830a3156bc9466b96b327c28268c", + "sha1": "7904f2aa3a357840ae49cbeb09842f4483d5b928", "gitDir": "test/corpus/repos/javascript", - "sha2": "386ca91fda91b11ea0302eb7ccf1fa23b32599c9" + "sha2": "f967788b85cc219d33d64545d8f1168ba3b43344" } ,{ "testCaseDescription": "javascript-nested-functions-delete-replacement-test", @@ -245,7 +234,6 @@ 1, 1 ], - "filepath": "nested-functions.js", "end": [ 1, 103 @@ -262,7 +250,6 @@ 2, 1 ], - "filepath": "nested-functions.js", "end": [ 2, 103 @@ -279,7 +266,6 @@ 2, 1 ], - "filepath": "nested-functions.js", "end": [ 2, 103 @@ -296,9 +282,9 @@ "filePaths": [ "nested-functions.js" ], - "sha1": "386ca91fda91b11ea0302eb7ccf1fa23b32599c9", + "sha1": "f967788b85cc219d33d64545d8f1168ba3b43344", "gitDir": "test/corpus/repos/javascript", - "sha2": "02f7dd997d356724a49f41006ba705ce714add97" + "sha2": "a2a9a7ac4e107169142641d24a73e66725e9db9b" } ,{ "testCaseDescription": "javascript-nested-functions-delete-test", @@ -312,7 +298,6 @@ 1, 1 ], - "filepath": "nested-functions.js", "end": [ 1, 103 @@ -329,9 +314,9 @@ "filePaths": [ "nested-functions.js" ], - "sha1": "02f7dd997d356724a49f41006ba705ce714add97", + "sha1": "a2a9a7ac4e107169142641d24a73e66725e9db9b", "gitDir": "test/corpus/repos/javascript", - "sha2": "8e0ffb4e5f360207a86e6b7030a08985f51fb244" + "sha2": "49fdec7315d09e2ed03e0ae78e59593952d0b6d4" } ,{ "testCaseDescription": "javascript-nested-functions-delete-rest-test", @@ -345,7 +330,6 @@ 1, 1 ], - "filepath": "nested-functions.js", "end": [ 1, 103 @@ -362,7 +346,7 @@ "filePaths": [ "nested-functions.js" ], - "sha1": "8e0ffb4e5f360207a86e6b7030a08985f51fb244", + "sha1": "49fdec7315d09e2ed03e0ae78e59593952d0b6d4", "gitDir": "test/corpus/repos/javascript", - "sha2": "b164e3140b16e2db3539cc769b9c60b0cc40912b" + "sha2": "f49e31811346eb6451409e09e36f417aeeda390a" }] diff --git a/test/corpus/diff-summaries/javascript/null.json b/test/corpus/diff-summaries/javascript/null.json index c0455672a..01061419d 100644 --- a/test/corpus/diff-summaries/javascript/null.json +++ b/test/corpus/diff-summaries/javascript/null.json @@ -10,7 +10,6 @@ 1, 1 ], - "filepath": "null.js", "end": [ 1, 5 @@ -27,9 +26,9 @@ "filePaths": [ "null.js" ], - "sha1": "0778d978feeb2e6973ff377ef502edef0f0ad001", + "sha1": "e56eea84017cd965ac9d95cdc5c5e95a89d7d4e4", "gitDir": "test/corpus/repos/javascript", - "sha2": "3760947053f1b923b93d4649bdc6e304839a5368" + "sha2": "3c20e1e7979eb2887701b29dc8774624e2a26aad" } ,{ "testCaseDescription": "javascript-null-replacement-insert-test", @@ -43,7 +42,6 @@ 1, 1 ], - "filepath": "null.js", "end": [ 1, 13 @@ -60,7 +58,6 @@ 2, 1 ], - "filepath": "null.js", "end": [ 2, 5 @@ -77,9 +74,9 @@ "filePaths": [ "null.js" ], - "sha1": "3760947053f1b923b93d4649bdc6e304839a5368", + "sha1": "3c20e1e7979eb2887701b29dc8774624e2a26aad", "gitDir": "test/corpus/repos/javascript", - "sha2": "fc90b8dede4be42ca9195458449fa2209166f87f" + "sha2": "889e6f6a91e48a97e5c6f56aedecbffe19b74576" } ,{ "testCaseDescription": "javascript-null-delete-insert-test", @@ -93,7 +90,6 @@ 1, 1 ], - "filepath": "null.js", "end": [ 1, 5 @@ -110,7 +106,6 @@ 1, 1 ], - "filepath": "null.js", "end": [ 1, 13 @@ -127,9 +122,9 @@ "filePaths": [ "null.js" ], - "sha1": "fc90b8dede4be42ca9195458449fa2209166f87f", + "sha1": "889e6f6a91e48a97e5c6f56aedecbffe19b74576", "gitDir": "test/corpus/repos/javascript", - "sha2": "3d1a432258a7aa0547b04636613213a7cf56f666" + "sha2": "3b8e6eab1f7a1c5ed97eecc60850b73900c79d85" } ,{ "testCaseDescription": "javascript-null-replacement-test", @@ -143,7 +138,6 @@ 1, 1 ], - "filepath": "null.js", "end": [ 1, 13 @@ -160,7 +154,6 @@ 1, 1 ], - "filepath": "null.js", "end": [ 1, 5 @@ -177,9 +170,9 @@ "filePaths": [ "null.js" ], - "sha1": "3d1a432258a7aa0547b04636613213a7cf56f666", + "sha1": "3b8e6eab1f7a1c5ed97eecc60850b73900c79d85", "gitDir": "test/corpus/repos/javascript", - "sha2": "d822fd650e1b13c829008a3f56324ba53dbe8a73" + "sha2": "93e4edaad54b8a1afce14e4540858e2f48b70f1f" } ,{ "testCaseDescription": "javascript-null-delete-replacement-test", @@ -193,7 +186,6 @@ 1, 1 ], - "filepath": "null.js", "end": [ 1, 13 @@ -210,7 +202,6 @@ 2, 1 ], - "filepath": "null.js", "end": [ 2, 5 @@ -227,7 +218,6 @@ 2, 1 ], - "filepath": "null.js", "end": [ 2, 13 @@ -244,9 +234,9 @@ "filePaths": [ "null.js" ], - "sha1": "d822fd650e1b13c829008a3f56324ba53dbe8a73", + "sha1": "93e4edaad54b8a1afce14e4540858e2f48b70f1f", "gitDir": "test/corpus/repos/javascript", - "sha2": "eaf7c8e93038557ac90e6196133c2d53a45d5926" + "sha2": "7401e97a5ae37d195acae99c6ca3f506ccc992db" } ,{ "testCaseDescription": "javascript-null-delete-test", @@ -260,7 +250,6 @@ 1, 1 ], - "filepath": "null.js", "end": [ 1, 5 @@ -277,9 +266,9 @@ "filePaths": [ "null.js" ], - "sha1": "eaf7c8e93038557ac90e6196133c2d53a45d5926", + "sha1": "7401e97a5ae37d195acae99c6ca3f506ccc992db", "gitDir": "test/corpus/repos/javascript", - "sha2": "3bda72523eb94abc8f50d5200829350586f968fa" + "sha2": "b44818542eea7ad12dd6644f2443f2df779d02d6" } ,{ "testCaseDescription": "javascript-null-delete-rest-test", @@ -293,7 +282,6 @@ 1, 1 ], - "filepath": "null.js", "end": [ 1, 13 @@ -310,7 +298,7 @@ "filePaths": [ "null.js" ], - "sha1": "3bda72523eb94abc8f50d5200829350586f968fa", + "sha1": "b44818542eea7ad12dd6644f2443f2df779d02d6", "gitDir": "test/corpus/repos/javascript", - "sha2": "a73ced91fe252bb89e890167a057a2e445e59bde" + "sha2": "330c4f8e410be65c3db4b801d5ca2e08094db242" }] diff --git a/test/corpus/diff-summaries/javascript/number.json b/test/corpus/diff-summaries/javascript/number.json index c2c7ae223..3052bd17c 100644 --- a/test/corpus/diff-summaries/javascript/number.json +++ b/test/corpus/diff-summaries/javascript/number.json @@ -10,7 +10,6 @@ 1, 1 ], - "filepath": "number.js", "end": [ 1, 4 @@ -27,9 +26,9 @@ "filePaths": [ "number.js" ], - "sha1": "8c3a25d3f1bc62ec49426bfddb5dfebf4d064d69", + "sha1": "ca76e71a73a3fb506699ae2ab0b98373e649850c", "gitDir": "test/corpus/repos/javascript", - "sha2": "a9b27fe7220b573b1d7ef2c18f291b7c44a901c5" + "sha2": "bca56807756346d5d207d0cf13f370ad60138dd3" } ,{ "testCaseDescription": "javascript-number-replacement-insert-test", @@ -43,7 +42,6 @@ 1, 1 ], - "filepath": "number.js", "end": [ 1, 4 @@ -60,7 +58,6 @@ 2, 1 ], - "filepath": "number.js", "end": [ 2, 4 @@ -77,9 +74,9 @@ "filePaths": [ "number.js" ], - "sha1": "a9b27fe7220b573b1d7ef2c18f291b7c44a901c5", + "sha1": "bca56807756346d5d207d0cf13f370ad60138dd3", "gitDir": "test/corpus/repos/javascript", - "sha2": "85bf2cc4b85b6b6c4b9e38587080cf279fbfd27c" + "sha2": "9e399dcad95c785376aecfb4c06c940f505ed776" } ,{ "testCaseDescription": "javascript-number-delete-insert-test", @@ -94,7 +91,6 @@ 1, 1 ], - "filepath": "number.js", "end": [ 1, 4 @@ -105,7 +101,6 @@ 1, 1 ], - "filepath": "number.js", "end": [ 1, 4 @@ -123,9 +118,9 @@ "filePaths": [ "number.js" ], - "sha1": "85bf2cc4b85b6b6c4b9e38587080cf279fbfd27c", + "sha1": "9e399dcad95c785376aecfb4c06c940f505ed776", "gitDir": "test/corpus/repos/javascript", - "sha2": "0792e9f13629071d94942f267a8b796b951f2b2e" + "sha2": "6333d7aab6347646f5411a86be2d868c9c19f715" } ,{ "testCaseDescription": "javascript-number-replacement-test", @@ -140,7 +135,6 @@ 1, 1 ], - "filepath": "number.js", "end": [ 1, 4 @@ -151,7 +145,6 @@ 1, 1 ], - "filepath": "number.js", "end": [ 1, 4 @@ -169,9 +162,9 @@ "filePaths": [ "number.js" ], - "sha1": "0792e9f13629071d94942f267a8b796b951f2b2e", + "sha1": "6333d7aab6347646f5411a86be2d868c9c19f715", "gitDir": "test/corpus/repos/javascript", - "sha2": "110953672844a606b3bec0d2c82e600d27f32289" + "sha2": "cfd5fe8a3286eccda307f09fc25a504539b1cf7e" } ,{ "testCaseDescription": "javascript-number-delete-replacement-test", @@ -185,7 +178,6 @@ 1, 1 ], - "filepath": "number.js", "end": [ 1, 4 @@ -202,7 +194,6 @@ 2, 1 ], - "filepath": "number.js", "end": [ 2, 4 @@ -219,7 +210,6 @@ 2, 1 ], - "filepath": "number.js", "end": [ 2, 4 @@ -236,9 +226,9 @@ "filePaths": [ "number.js" ], - "sha1": "110953672844a606b3bec0d2c82e600d27f32289", + "sha1": "cfd5fe8a3286eccda307f09fc25a504539b1cf7e", "gitDir": "test/corpus/repos/javascript", - "sha2": "d17f9f957da8c550558ac21e41112f904a192b60" + "sha2": "fe9b3523d02afb88ae0bddf29eab6d2af8f135fa" } ,{ "testCaseDescription": "javascript-number-delete-test", @@ -252,7 +242,6 @@ 1, 1 ], - "filepath": "number.js", "end": [ 1, 4 @@ -269,9 +258,9 @@ "filePaths": [ "number.js" ], - "sha1": "d17f9f957da8c550558ac21e41112f904a192b60", + "sha1": "fe9b3523d02afb88ae0bddf29eab6d2af8f135fa", "gitDir": "test/corpus/repos/javascript", - "sha2": "c79e586b611cfb27e464176a536f2044bebc40f9" + "sha2": "5f00cbbdbcc8c05786b5aa95f9b909fd0f3652cf" } ,{ "testCaseDescription": "javascript-number-delete-rest-test", @@ -285,7 +274,6 @@ 1, 1 ], - "filepath": "number.js", "end": [ 1, 4 @@ -302,7 +290,7 @@ "filePaths": [ "number.js" ], - "sha1": "c79e586b611cfb27e464176a536f2044bebc40f9", + "sha1": "5f00cbbdbcc8c05786b5aa95f9b909fd0f3652cf", "gitDir": "test/corpus/repos/javascript", - "sha2": "c7aab3785be8b3fb5f2a62f600201f094b46e55b" + "sha2": "9f0cec39421594e76f56c7843f9902d1e840dcaa" }] diff --git a/test/corpus/diff-summaries/javascript/object-with-methods.json b/test/corpus/diff-summaries/javascript/object-with-methods.json index fe9b3599c..f2e7bc5c0 100644 --- a/test/corpus/diff-summaries/javascript/object-with-methods.json +++ b/test/corpus/diff-summaries/javascript/object-with-methods.json @@ -10,7 +10,6 @@ 1, 1 ], - "filepath": "objects-with-methods.js", "end": [ 1, 32 @@ -27,9 +26,9 @@ "filePaths": [ "objects-with-methods.js" ], - "sha1": "f9fa9489012e03e0ba9e457e290b45d3876c02e6", + "sha1": "f13aef7dcdfe65826b6d93b4b371afe29a12f21f", "gitDir": "test/corpus/repos/javascript", - "sha2": "6108fee4a861880a4b02bf5fb1e9f5ed096d24a4" + "sha2": "96b548baab802a6e28144b588e564b28ff84ac55" } ,{ "testCaseDescription": "javascript-objects-with-methods-replacement-insert-test", @@ -43,7 +42,6 @@ 1, 1 ], - "filepath": "objects-with-methods.js", "end": [ 1, 37 @@ -60,7 +58,6 @@ 2, 1 ], - "filepath": "objects-with-methods.js", "end": [ 2, 32 @@ -77,9 +74,9 @@ "filePaths": [ "objects-with-methods.js" ], - "sha1": "6108fee4a861880a4b02bf5fb1e9f5ed096d24a4", + "sha1": "96b548baab802a6e28144b588e564b28ff84ac55", "gitDir": "test/corpus/repos/javascript", - "sha2": "372855e063f5f8949765f4223648b489e3472637" + "sha2": "1293592160bd09b7bc12a75581a7496a70bb8f81" } ,{ "testCaseDescription": "javascript-objects-with-methods-delete-insert-test", @@ -94,7 +91,6 @@ 1, 3 ], - "filepath": "objects-with-methods.js", "end": [ 1, 11 @@ -105,7 +101,6 @@ 1, 3 ], - "filepath": "objects-with-methods.js", "end": [ 1, 6 @@ -123,9 +118,9 @@ "filePaths": [ "objects-with-methods.js" ], - "sha1": "372855e063f5f8949765f4223648b489e3472637", + "sha1": "1293592160bd09b7bc12a75581a7496a70bb8f81", "gitDir": "test/corpus/repos/javascript", - "sha2": "1813d1915cb03d8fec802134aab74575e9e2fbec" + "sha2": "ee09bff08bb2a4467e2d2733db38fdc35a91fa01" } ,{ "testCaseDescription": "javascript-objects-with-methods-replacement-test", @@ -140,7 +135,6 @@ 1, 3 ], - "filepath": "objects-with-methods.js", "end": [ 1, 6 @@ -151,7 +145,6 @@ 1, 3 ], - "filepath": "objects-with-methods.js", "end": [ 1, 11 @@ -169,9 +162,9 @@ "filePaths": [ "objects-with-methods.js" ], - "sha1": "1813d1915cb03d8fec802134aab74575e9e2fbec", + "sha1": "ee09bff08bb2a4467e2d2733db38fdc35a91fa01", "gitDir": "test/corpus/repos/javascript", - "sha2": "28f4990c4ff3b9c0f7c4b5c846d2fcc0008ad7c4" + "sha2": "70c38b12df93c18958a2ff94145a5c1b8f64e0d1" } ,{ "testCaseDescription": "javascript-objects-with-methods-delete-replacement-test", @@ -185,7 +178,6 @@ 1, 1 ], - "filepath": "objects-with-methods.js", "end": [ 1, 37 @@ -202,7 +194,6 @@ 2, 1 ], - "filepath": "objects-with-methods.js", "end": [ 2, 32 @@ -219,7 +210,6 @@ 2, 1 ], - "filepath": "objects-with-methods.js", "end": [ 2, 37 @@ -236,9 +226,9 @@ "filePaths": [ "objects-with-methods.js" ], - "sha1": "28f4990c4ff3b9c0f7c4b5c846d2fcc0008ad7c4", + "sha1": "70c38b12df93c18958a2ff94145a5c1b8f64e0d1", "gitDir": "test/corpus/repos/javascript", - "sha2": "f5fe20d829ca8e47eba06cdac286cd542d4d1a41" + "sha2": "c9f20856166b00c740c53d34289d5bdafcfe73f8" } ,{ "testCaseDescription": "javascript-objects-with-methods-delete-test", @@ -252,7 +242,6 @@ 1, 1 ], - "filepath": "objects-with-methods.js", "end": [ 1, 32 @@ -269,9 +258,9 @@ "filePaths": [ "objects-with-methods.js" ], - "sha1": "f5fe20d829ca8e47eba06cdac286cd542d4d1a41", + "sha1": "c9f20856166b00c740c53d34289d5bdafcfe73f8", "gitDir": "test/corpus/repos/javascript", - "sha2": "380c12fa56e7333f635d55f5a9a1f476990ec6a2" + "sha2": "f8a7132e504b1bf9154a8946db3bc7a412c3e983" } ,{ "testCaseDescription": "javascript-objects-with-methods-delete-rest-test", @@ -285,7 +274,6 @@ 1, 1 ], - "filepath": "objects-with-methods.js", "end": [ 1, 37 @@ -302,7 +290,7 @@ "filePaths": [ "objects-with-methods.js" ], - "sha1": "380c12fa56e7333f635d55f5a9a1f476990ec6a2", + "sha1": "f8a7132e504b1bf9154a8946db3bc7a412c3e983", "gitDir": "test/corpus/repos/javascript", - "sha2": "b7ff6b2fd2253011bcaadd23ed546003c4bbd5b3" + "sha2": "179d020d71ae2d25e7da3fa6af1db307411db219" }] diff --git a/test/corpus/diff-summaries/javascript/object.json b/test/corpus/diff-summaries/javascript/object.json index 36f651195..3222f85f1 100644 --- a/test/corpus/diff-summaries/javascript/object.json +++ b/test/corpus/diff-summaries/javascript/object.json @@ -10,7 +10,6 @@ 1, 1 ], - "filepath": "object.js", "end": [ 1, 21 @@ -27,9 +26,9 @@ "filePaths": [ "object.js" ], - "sha1": "9455d4cb158d3f5131c688e7909b842436c06205", + "sha1": "f58cfc7947653db85574d1569f494d8b11791ad1", "gitDir": "test/corpus/repos/javascript", - "sha2": "b3b28aec78513965c8813790529e04ec9e18ed8f" + "sha2": "6f20c6eb26c60838e377075ef27fe3b76b98dd26" } ,{ "testCaseDescription": "javascript-object-replacement-insert-test", @@ -43,7 +42,6 @@ 1, 1 ], - "filepath": "object.js", "end": [ 1, 54 @@ -60,7 +58,6 @@ 2, 1 ], - "filepath": "object.js", "end": [ 2, 21 @@ -77,9 +74,9 @@ "filePaths": [ "object.js" ], - "sha1": "b3b28aec78513965c8813790529e04ec9e18ed8f", + "sha1": "6f20c6eb26c60838e377075ef27fe3b76b98dd26", "gitDir": "test/corpus/repos/javascript", - "sha2": "e1bbcc717583d7055af827a27c1d795889bc4efb" + "sha2": "32fccdccdc5ff2d5c4878563744f146e423e812d" } ,{ "testCaseDescription": "javascript-object-delete-insert-test", @@ -93,7 +90,6 @@ 1, 21 ], - "filepath": "object.js", "end": [ 1, 37 @@ -110,7 +106,6 @@ 1, 39 ], - "filepath": "object.js", "end": [ 1, 52 @@ -127,9 +122,9 @@ "filePaths": [ "object.js" ], - "sha1": "e1bbcc717583d7055af827a27c1d795889bc4efb", + "sha1": "32fccdccdc5ff2d5c4878563744f146e423e812d", "gitDir": "test/corpus/repos/javascript", - "sha2": "5c811c46054adeed885741e626aaaa41249da6d5" + "sha2": "af8db674db1087a5f2953ccfe17ba15b840f6e76" } ,{ "testCaseDescription": "javascript-object-replacement-test", @@ -143,7 +138,6 @@ 1, 21 ], - "filepath": "object.js", "end": [ 1, 37 @@ -160,7 +154,6 @@ 1, 39 ], - "filepath": "object.js", "end": [ 1, 52 @@ -177,9 +170,9 @@ "filePaths": [ "object.js" ], - "sha1": "5c811c46054adeed885741e626aaaa41249da6d5", + "sha1": "af8db674db1087a5f2953ccfe17ba15b840f6e76", "gitDir": "test/corpus/repos/javascript", - "sha2": "d5dbee2076d579465c4a2ceba657047f04d03e64" + "sha2": "684501429d36cd64a92cbec1c777560cad857469" } ,{ "testCaseDescription": "javascript-object-delete-replacement-test", @@ -193,7 +186,6 @@ 1, 1 ], - "filepath": "object.js", "end": [ 1, 54 @@ -210,7 +202,6 @@ 2, 1 ], - "filepath": "object.js", "end": [ 2, 21 @@ -227,7 +218,6 @@ 2, 1 ], - "filepath": "object.js", "end": [ 2, 54 @@ -244,9 +234,9 @@ "filePaths": [ "object.js" ], - "sha1": "d5dbee2076d579465c4a2ceba657047f04d03e64", + "sha1": "684501429d36cd64a92cbec1c777560cad857469", "gitDir": "test/corpus/repos/javascript", - "sha2": "7419753061516443955b4ee7580a8502f053bbd2" + "sha2": "b1a8ced66b7504d887f621ef64db91e3ec0d5674" } ,{ "testCaseDescription": "javascript-object-delete-test", @@ -260,7 +250,6 @@ 1, 1 ], - "filepath": "object.js", "end": [ 1, 21 @@ -277,9 +266,9 @@ "filePaths": [ "object.js" ], - "sha1": "7419753061516443955b4ee7580a8502f053bbd2", + "sha1": "b1a8ced66b7504d887f621ef64db91e3ec0d5674", "gitDir": "test/corpus/repos/javascript", - "sha2": "cdeac17b9827c7036f86b58e265eac8245142a19" + "sha2": "02afb244f44208b28e12483be548a9b8478bb5ec" } ,{ "testCaseDescription": "javascript-object-delete-rest-test", @@ -293,7 +282,6 @@ 1, 1 ], - "filepath": "object.js", "end": [ 1, 54 @@ -310,7 +298,7 @@ "filePaths": [ "object.js" ], - "sha1": "cdeac17b9827c7036f86b58e265eac8245142a19", + "sha1": "02afb244f44208b28e12483be548a9b8478bb5ec", "gitDir": "test/corpus/repos/javascript", - "sha2": "b33f47fbe6d253fd1ee502cda8ef5cd4bd771b42" + "sha2": "4f744373cdf308bd96fa3eec09679a7f6461d5aa" }] diff --git a/test/corpus/diff-summaries/javascript/regex.json b/test/corpus/diff-summaries/javascript/regex.json index 8ddf1354e..9101e11c4 100644 --- a/test/corpus/diff-summaries/javascript/regex.json +++ b/test/corpus/diff-summaries/javascript/regex.json @@ -10,7 +10,6 @@ 1, 1 ], - "filepath": "regex.js", "end": [ 1, 7 @@ -27,9 +26,9 @@ "filePaths": [ "regex.js" ], - "sha1": "058fa89622b13938f1d49514c08fc3297f2654b2", + "sha1": "8e70c5571d07dc7e882e979cd7432bc275ddb4d2", "gitDir": "test/corpus/repos/javascript", - "sha2": "2ac5e42c57f184a28b6d41529a6f372fb950b575" + "sha2": "4c83ca78814534d5a2bc1b79686682eb348ce742" } ,{ "testCaseDescription": "javascript-regex-replacement-insert-test", @@ -43,7 +42,6 @@ 1, 1 ], - "filepath": "regex.js", "end": [ 1, 15 @@ -60,7 +58,6 @@ 2, 1 ], - "filepath": "regex.js", "end": [ 2, 7 @@ -77,9 +74,9 @@ "filePaths": [ "regex.js" ], - "sha1": "2ac5e42c57f184a28b6d41529a6f372fb950b575", + "sha1": "4c83ca78814534d5a2bc1b79686682eb348ce742", "gitDir": "test/corpus/repos/javascript", - "sha2": "434fd4b4e2785ad4e6103a644a6638740695993a" + "sha2": "7fa1b99e3e5b9c27a8d17d12149674474c053109" } ,{ "testCaseDescription": "javascript-regex-delete-insert-test", @@ -94,7 +91,6 @@ 1, 1 ], - "filepath": "regex.js", "end": [ 1, 15 @@ -105,7 +101,6 @@ 1, 1 ], - "filepath": "regex.js", "end": [ 1, 7 @@ -123,9 +118,9 @@ "filePaths": [ "regex.js" ], - "sha1": "434fd4b4e2785ad4e6103a644a6638740695993a", + "sha1": "7fa1b99e3e5b9c27a8d17d12149674474c053109", "gitDir": "test/corpus/repos/javascript", - "sha2": "f44dca31eb249f2c11f5bcccc337d79733dbb822" + "sha2": "a4e9e5c8515b7454ffddd1033ed36517bbeddeb9" } ,{ "testCaseDescription": "javascript-regex-replacement-test", @@ -140,7 +135,6 @@ 1, 1 ], - "filepath": "regex.js", "end": [ 1, 7 @@ -151,7 +145,6 @@ 1, 1 ], - "filepath": "regex.js", "end": [ 1, 15 @@ -169,9 +162,9 @@ "filePaths": [ "regex.js" ], - "sha1": "f44dca31eb249f2c11f5bcccc337d79733dbb822", + "sha1": "a4e9e5c8515b7454ffddd1033ed36517bbeddeb9", "gitDir": "test/corpus/repos/javascript", - "sha2": "9cc5633cd9ae0b8fc3f8dbf476967672f641c7de" + "sha2": "a2874c1175ad7bf7afe04fae6708c46648ec94c9" } ,{ "testCaseDescription": "javascript-regex-delete-replacement-test", @@ -185,7 +178,6 @@ 1, 1 ], - "filepath": "regex.js", "end": [ 1, 15 @@ -202,7 +194,6 @@ 2, 1 ], - "filepath": "regex.js", "end": [ 2, 7 @@ -219,7 +210,6 @@ 2, 1 ], - "filepath": "regex.js", "end": [ 2, 15 @@ -236,9 +226,9 @@ "filePaths": [ "regex.js" ], - "sha1": "9cc5633cd9ae0b8fc3f8dbf476967672f641c7de", + "sha1": "a2874c1175ad7bf7afe04fae6708c46648ec94c9", "gitDir": "test/corpus/repos/javascript", - "sha2": "fbd21661edc45d081f13320b56301b396164325d" + "sha2": "5360c30a93987c13ebaa73a3836e2574d7f62911" } ,{ "testCaseDescription": "javascript-regex-delete-test", @@ -252,7 +242,6 @@ 1, 1 ], - "filepath": "regex.js", "end": [ 1, 7 @@ -269,9 +258,9 @@ "filePaths": [ "regex.js" ], - "sha1": "fbd21661edc45d081f13320b56301b396164325d", + "sha1": "5360c30a93987c13ebaa73a3836e2574d7f62911", "gitDir": "test/corpus/repos/javascript", - "sha2": "f29cd34d232de2b5bc5837bb7712f9f40912a12f" + "sha2": "1ae109a0e48e288712ef93815129152e6bcf1098" } ,{ "testCaseDescription": "javascript-regex-delete-rest-test", @@ -285,7 +274,6 @@ 1, 1 ], - "filepath": "regex.js", "end": [ 1, 15 @@ -302,7 +290,7 @@ "filePaths": [ "regex.js" ], - "sha1": "f29cd34d232de2b5bc5837bb7712f9f40912a12f", + "sha1": "1ae109a0e48e288712ef93815129152e6bcf1098", "gitDir": "test/corpus/repos/javascript", - "sha2": "41251fa1af46b7fe46270fa62626832e6d95fb19" + "sha2": "4c21f4aa629b89eee95c9af81f90075ffda6d99f" }] diff --git a/test/corpus/diff-summaries/javascript/relational-operator.json b/test/corpus/diff-summaries/javascript/relational-operator.json index 9018f9e2d..3c144ab23 100644 --- a/test/corpus/diff-summaries/javascript/relational-operator.json +++ b/test/corpus/diff-summaries/javascript/relational-operator.json @@ -10,7 +10,6 @@ 1, 1 ], - "filepath": "relational-operator.js", "end": [ 1, 6 @@ -27,9 +26,9 @@ "filePaths": [ "relational-operator.js" ], - "sha1": "aa8e5d0cc9ed22261dd69958752f86537aa464da", + "sha1": "4acf98d6af3ab5b912b92b9b2f89018fd768fff9", "gitDir": "test/corpus/repos/javascript", - "sha2": "fb88f6e2f5970402b70df21786e65701a017bfa3" + "sha2": "aeccebdb301fe1d07cb1644a3fbafa46388245a1" } ,{ "testCaseDescription": "javascript-relational-operator-replacement-insert-test", @@ -43,7 +42,6 @@ 1, 1 ], - "filepath": "relational-operator.js", "end": [ 1, 7 @@ -60,7 +58,6 @@ 2, 1 ], - "filepath": "relational-operator.js", "end": [ 2, 6 @@ -77,9 +74,9 @@ "filePaths": [ "relational-operator.js" ], - "sha1": "fb88f6e2f5970402b70df21786e65701a017bfa3", + "sha1": "aeccebdb301fe1d07cb1644a3fbafa46388245a1", "gitDir": "test/corpus/repos/javascript", - "sha2": "904b878d80d4eb3e1902f406ff8bc940529513d0" + "sha2": "fc6247ea42d8bdd48b5f8aee0b1719d14fd587a4" } ,{ "testCaseDescription": "javascript-relational-operator-delete-insert-test", @@ -90,9 +87,9 @@ "filePaths": [ "relational-operator.js" ], - "sha1": "904b878d80d4eb3e1902f406ff8bc940529513d0", + "sha1": "fc6247ea42d8bdd48b5f8aee0b1719d14fd587a4", "gitDir": "test/corpus/repos/javascript", - "sha2": "2974eb735b931584ff0c0112fefae5277f3c6f25" + "sha2": "6cba37e613638e9679495cf0e5c46a8f8388a4ba" } ,{ "testCaseDescription": "javascript-relational-operator-replacement-test", @@ -103,9 +100,9 @@ "filePaths": [ "relational-operator.js" ], - "sha1": "2974eb735b931584ff0c0112fefae5277f3c6f25", + "sha1": "6cba37e613638e9679495cf0e5c46a8f8388a4ba", "gitDir": "test/corpus/repos/javascript", - "sha2": "e302597d2f16e8aeac7153523995575596565c45" + "sha2": "1b647600a0425c2f8e412974d26807ae663e1bb8" } ,{ "testCaseDescription": "javascript-relational-operator-delete-replacement-test", @@ -119,7 +116,6 @@ 1, 1 ], - "filepath": "relational-operator.js", "end": [ 1, 7 @@ -136,9 +132,9 @@ "filePaths": [ "relational-operator.js" ], - "sha1": "e302597d2f16e8aeac7153523995575596565c45", + "sha1": "1b647600a0425c2f8e412974d26807ae663e1bb8", "gitDir": "test/corpus/repos/javascript", - "sha2": "64982abd1a0575f8b9eaece8a71267a4474e7cff" + "sha2": "1bd11093bcd52881234e023bd8edc7a8689cc180" } ,{ "testCaseDescription": "javascript-relational-operator-delete-test", @@ -152,7 +148,6 @@ 1, 1 ], - "filepath": "relational-operator.js", "end": [ 1, 6 @@ -169,9 +164,9 @@ "filePaths": [ "relational-operator.js" ], - "sha1": "64982abd1a0575f8b9eaece8a71267a4474e7cff", + "sha1": "1bd11093bcd52881234e023bd8edc7a8689cc180", "gitDir": "test/corpus/repos/javascript", - "sha2": "d93e8a55a799042669cdbfc5414c5f69337ec20b" + "sha2": "60c48ce65a7d4c71ee356f684a096e6c597a2bd3" } ,{ "testCaseDescription": "javascript-relational-operator-delete-rest-test", @@ -185,7 +180,6 @@ 1, 1 ], - "filepath": "relational-operator.js", "end": [ 1, 7 @@ -202,7 +196,7 @@ "filePaths": [ "relational-operator.js" ], - "sha1": "d93e8a55a799042669cdbfc5414c5f69337ec20b", + "sha1": "60c48ce65a7d4c71ee356f684a096e6c597a2bd3", "gitDir": "test/corpus/repos/javascript", - "sha2": "acf5deeacb1725969d9840d8f43633df395e5dcc" + "sha2": "3c62d32d99e94fd0ece751f530c6b37fe10b1775" }] diff --git a/test/corpus/diff-summaries/javascript/return-statement.json b/test/corpus/diff-summaries/javascript/return-statement.json index a3c545361..f640cdae1 100644 --- a/test/corpus/diff-summaries/javascript/return-statement.json +++ b/test/corpus/diff-summaries/javascript/return-statement.json @@ -10,7 +10,6 @@ 1, 1 ], - "filepath": "return-statement.js", "end": [ 1, 10 @@ -27,9 +26,9 @@ "filePaths": [ "return-statement.js" ], - "sha1": "4b2b35f5d9900e04b167abcf83c279790a555fa4", + "sha1": "72327cf998fb96cc493108b069500422561c0d1d", "gitDir": "test/corpus/repos/javascript", - "sha2": "db054b4b9c7ad3d23956cfaf589b3f8189a65874" + "sha2": "e23ed05e0a1eea7ef2688e138b8bbb0bd10fb04e" } ,{ "testCaseDescription": "javascript-return-statement-replacement-insert-test", @@ -43,7 +42,6 @@ 1, 1 ], - "filepath": "return-statement.js", "end": [ 1, 8 @@ -60,7 +58,6 @@ 2, 1 ], - "filepath": "return-statement.js", "end": [ 2, 10 @@ -77,9 +74,9 @@ "filePaths": [ "return-statement.js" ], - "sha1": "db054b4b9c7ad3d23956cfaf589b3f8189a65874", + "sha1": "e23ed05e0a1eea7ef2688e138b8bbb0bd10fb04e", "gitDir": "test/corpus/repos/javascript", - "sha2": "37daa0a914f5344568e98f4bb34795c10785728f" + "sha2": "4e05c84099b05aad16ab8d737c17122625fcaf49" } ,{ "testCaseDescription": "javascript-return-statement-delete-insert-test", @@ -93,7 +90,6 @@ 1, 8 ], - "filepath": "return-statement.js", "end": [ 1, 9 @@ -110,9 +106,9 @@ "filePaths": [ "return-statement.js" ], - "sha1": "37daa0a914f5344568e98f4bb34795c10785728f", + "sha1": "4e05c84099b05aad16ab8d737c17122625fcaf49", "gitDir": "test/corpus/repos/javascript", - "sha2": "beff32aae75a8c9f0a6c8689a117fe99bfcffefa" + "sha2": "36f5ecef5e20cfad01f4b5612458ee7d1994fce4" } ,{ "testCaseDescription": "javascript-return-statement-replacement-test", @@ -126,7 +122,6 @@ 1, 8 ], - "filepath": "return-statement.js", "end": [ 1, 9 @@ -143,9 +138,9 @@ "filePaths": [ "return-statement.js" ], - "sha1": "beff32aae75a8c9f0a6c8689a117fe99bfcffefa", + "sha1": "36f5ecef5e20cfad01f4b5612458ee7d1994fce4", "gitDir": "test/corpus/repos/javascript", - "sha2": "75aaf6801e8dbecd5580441db2bf222110a9726c" + "sha2": "20288d9df5198cd8c73654f4a897f0ed9a60aaa2" } ,{ "testCaseDescription": "javascript-return-statement-delete-replacement-test", @@ -159,7 +154,6 @@ 1, 1 ], - "filepath": "return-statement.js", "end": [ 1, 8 @@ -176,7 +170,6 @@ 2, 1 ], - "filepath": "return-statement.js", "end": [ 2, 10 @@ -193,7 +186,6 @@ 2, 1 ], - "filepath": "return-statement.js", "end": [ 2, 8 @@ -210,9 +202,9 @@ "filePaths": [ "return-statement.js" ], - "sha1": "75aaf6801e8dbecd5580441db2bf222110a9726c", + "sha1": "20288d9df5198cd8c73654f4a897f0ed9a60aaa2", "gitDir": "test/corpus/repos/javascript", - "sha2": "6b038394964036d1e240c85a55be62fbfd638d62" + "sha2": "af618a971319f4d867380cbf2582056e05413159" } ,{ "testCaseDescription": "javascript-return-statement-delete-test", @@ -226,7 +218,6 @@ 1, 1 ], - "filepath": "return-statement.js", "end": [ 1, 10 @@ -243,9 +234,9 @@ "filePaths": [ "return-statement.js" ], - "sha1": "6b038394964036d1e240c85a55be62fbfd638d62", + "sha1": "af618a971319f4d867380cbf2582056e05413159", "gitDir": "test/corpus/repos/javascript", - "sha2": "5291abc5d7e6a27de845cd2be7e7ff7dbda978e3" + "sha2": "5b70922a7bd2b32e0f89e752523055823e55579b" } ,{ "testCaseDescription": "javascript-return-statement-delete-rest-test", @@ -259,7 +250,6 @@ 1, 1 ], - "filepath": "return-statement.js", "end": [ 1, 8 @@ -276,7 +266,7 @@ "filePaths": [ "return-statement.js" ], - "sha1": "5291abc5d7e6a27de845cd2be7e7ff7dbda978e3", + "sha1": "5b70922a7bd2b32e0f89e752523055823e55579b", "gitDir": "test/corpus/repos/javascript", - "sha2": "654be5306d35ca185023c542852d13f395b9233d" + "sha2": "937643815a14601103a1ba1fcf99a82306f52ace" }] diff --git a/test/corpus/diff-summaries/javascript/string.json b/test/corpus/diff-summaries/javascript/string.json index 78d2c0cb3..e4ffb184c 100644 --- a/test/corpus/diff-summaries/javascript/string.json +++ b/test/corpus/diff-summaries/javascript/string.json @@ -10,7 +10,6 @@ 1, 1 ], - "filepath": "string.js", "end": [ 1, 32 @@ -27,9 +26,9 @@ "filePaths": [ "string.js" ], - "sha1": "b7ff6b2fd2253011bcaadd23ed546003c4bbd5b3", + "sha1": "b8f8704eac31cd6cb8a2d60bc6432cd69336e7ca", "gitDir": "test/corpus/repos/javascript", - "sha2": "e5806edc379e2443e048b4a8a6d9d5cc59ed72be" + "sha2": "1eac803d3d86b8fa340350c56d2eb7d39d6d7342" } ,{ "testCaseDescription": "javascript-string-replacement-insert-test", @@ -43,7 +42,6 @@ 1, 1 ], - "filepath": "string.js", "end": [ 1, 42 @@ -60,7 +58,6 @@ 2, 1 ], - "filepath": "string.js", "end": [ 2, 32 @@ -77,9 +74,9 @@ "filePaths": [ "string.js" ], - "sha1": "e5806edc379e2443e048b4a8a6d9d5cc59ed72be", + "sha1": "1eac803d3d86b8fa340350c56d2eb7d39d6d7342", "gitDir": "test/corpus/repos/javascript", - "sha2": "c2d8ba6ff8567ce44d1039c61610225832829c75" + "sha2": "350a048f1d418381f48bdf81e353496de8248e0d" } ,{ "testCaseDescription": "javascript-string-delete-insert-test", @@ -94,7 +91,6 @@ 1, 1 ], - "filepath": "string.js", "end": [ 1, 42 @@ -105,7 +101,6 @@ 1, 1 ], - "filepath": "string.js", "end": [ 1, 32 @@ -123,9 +118,9 @@ "filePaths": [ "string.js" ], - "sha1": "c2d8ba6ff8567ce44d1039c61610225832829c75", + "sha1": "350a048f1d418381f48bdf81e353496de8248e0d", "gitDir": "test/corpus/repos/javascript", - "sha2": "4610ad3d178bb583477571492c6af18e05ca901a" + "sha2": "74081edf9644d5f3e98ccf41140ebda1f2b82bc6" } ,{ "testCaseDescription": "javascript-string-replacement-test", @@ -140,7 +135,6 @@ 1, 1 ], - "filepath": "string.js", "end": [ 1, 32 @@ -151,7 +145,6 @@ 1, 1 ], - "filepath": "string.js", "end": [ 1, 42 @@ -169,9 +162,9 @@ "filePaths": [ "string.js" ], - "sha1": "4610ad3d178bb583477571492c6af18e05ca901a", + "sha1": "74081edf9644d5f3e98ccf41140ebda1f2b82bc6", "gitDir": "test/corpus/repos/javascript", - "sha2": "ec101398fcff547df16980ef5d082a8904cd38e2" + "sha2": "67dce6ee4390c8826050dbb0dcd1afb9e0c5ff38" } ,{ "testCaseDescription": "javascript-string-delete-replacement-test", @@ -185,7 +178,6 @@ 1, 1 ], - "filepath": "string.js", "end": [ 1, 42 @@ -202,7 +194,6 @@ 2, 1 ], - "filepath": "string.js", "end": [ 2, 32 @@ -219,7 +210,6 @@ 2, 1 ], - "filepath": "string.js", "end": [ 2, 42 @@ -236,9 +226,9 @@ "filePaths": [ "string.js" ], - "sha1": "ec101398fcff547df16980ef5d082a8904cd38e2", + "sha1": "67dce6ee4390c8826050dbb0dcd1afb9e0c5ff38", "gitDir": "test/corpus/repos/javascript", - "sha2": "f168a15d67272a6917370b8569135761b3d2fdbd" + "sha2": "965488ad061223b589ff8388f3da6e539b60709a" } ,{ "testCaseDescription": "javascript-string-delete-test", @@ -252,7 +242,6 @@ 1, 1 ], - "filepath": "string.js", "end": [ 1, 32 @@ -269,9 +258,9 @@ "filePaths": [ "string.js" ], - "sha1": "f168a15d67272a6917370b8569135761b3d2fdbd", + "sha1": "965488ad061223b589ff8388f3da6e539b60709a", "gitDir": "test/corpus/repos/javascript", - "sha2": "5ec639edee9695155342720c519788e34584223b" + "sha2": "a53c564049237a36c0a19ae56698cb5587edcef9" } ,{ "testCaseDescription": "javascript-string-delete-rest-test", @@ -285,7 +274,6 @@ 1, 1 ], - "filepath": "string.js", "end": [ 1, 42 @@ -302,7 +290,7 @@ "filePaths": [ "string.js" ], - "sha1": "5ec639edee9695155342720c519788e34584223b", + "sha1": "a53c564049237a36c0a19ae56698cb5587edcef9", "gitDir": "test/corpus/repos/javascript", - "sha2": "8c3a25d3f1bc62ec49426bfddb5dfebf4d064d69" + "sha2": "ba4af0c2eb2e6c815e957def7e452a8f06765f94" }] diff --git a/test/corpus/diff-summaries/javascript/subscript-access-assignment.json b/test/corpus/diff-summaries/javascript/subscript-access-assignment.json index e9fed30e2..750dcb2b5 100644 --- a/test/corpus/diff-summaries/javascript/subscript-access-assignment.json +++ b/test/corpus/diff-summaries/javascript/subscript-access-assignment.json @@ -10,7 +10,6 @@ 1, 1 ], - "filepath": "subscript-access-assignment.js", "end": [ 1, 11 @@ -27,9 +26,9 @@ "filePaths": [ "subscript-access-assignment.js" ], - "sha1": "24df96dbbf63c7c9940c4c18cd4286ca25dae952", + "sha1": "017dd08471859c04fa5958753782e80f6b974bb4", "gitDir": "test/corpus/repos/javascript", - "sha2": "2e84457d7745d18b03e53ef5509b0ad54ba17cdb" + "sha2": "cc4a86eba8cdee2e08e6cff2030c5d2b7e677d8b" } ,{ "testCaseDescription": "javascript-subscript-access-assignment-replacement-insert-test", @@ -43,7 +42,6 @@ 1, 1 ], - "filepath": "subscript-access-assignment.js", "end": [ 1, 11 @@ -60,7 +58,6 @@ 2, 1 ], - "filepath": "subscript-access-assignment.js", "end": [ 2, 11 @@ -77,9 +74,9 @@ "filePaths": [ "subscript-access-assignment.js" ], - "sha1": "2e84457d7745d18b03e53ef5509b0ad54ba17cdb", + "sha1": "cc4a86eba8cdee2e08e6cff2030c5d2b7e677d8b", "gitDir": "test/corpus/repos/javascript", - "sha2": "c10878f68d963f8590a20a96decc7c9d46677ea4" + "sha2": "3705016f2c59cf2a7362e51f25a691619e63b0ef" } ,{ "testCaseDescription": "javascript-subscript-access-assignment-delete-insert-test", @@ -94,7 +91,6 @@ 1, 10 ], - "filepath": "subscript-access-assignment.js", "end": [ 1, 11 @@ -105,7 +101,6 @@ 1, 10 ], - "filepath": "subscript-access-assignment.js", "end": [ 1, 11 @@ -123,9 +118,9 @@ "filePaths": [ "subscript-access-assignment.js" ], - "sha1": "c10878f68d963f8590a20a96decc7c9d46677ea4", + "sha1": "3705016f2c59cf2a7362e51f25a691619e63b0ef", "gitDir": "test/corpus/repos/javascript", - "sha2": "b6c7d9e8ace1d878d63fb7d0fdea67b9d54dede8" + "sha2": "fd2d02ddfc93fb1668a6c5baf512b71ef369ea18" } ,{ "testCaseDescription": "javascript-subscript-access-assignment-replacement-test", @@ -140,7 +135,6 @@ 1, 10 ], - "filepath": "subscript-access-assignment.js", "end": [ 1, 11 @@ -151,7 +145,6 @@ 1, 10 ], - "filepath": "subscript-access-assignment.js", "end": [ 1, 11 @@ -169,9 +162,9 @@ "filePaths": [ "subscript-access-assignment.js" ], - "sha1": "b6c7d9e8ace1d878d63fb7d0fdea67b9d54dede8", + "sha1": "fd2d02ddfc93fb1668a6c5baf512b71ef369ea18", "gitDir": "test/corpus/repos/javascript", - "sha2": "692c5d641d8f57e45695b61eff927a180479f8be" + "sha2": "e4665c506aad21e4dcc6a8b7062581abe3bf62a0" } ,{ "testCaseDescription": "javascript-subscript-access-assignment-delete-replacement-test", @@ -185,7 +178,6 @@ 1, 1 ], - "filepath": "subscript-access-assignment.js", "end": [ 1, 11 @@ -202,7 +194,6 @@ 2, 1 ], - "filepath": "subscript-access-assignment.js", "end": [ 2, 11 @@ -219,7 +210,6 @@ 2, 1 ], - "filepath": "subscript-access-assignment.js", "end": [ 2, 11 @@ -236,9 +226,9 @@ "filePaths": [ "subscript-access-assignment.js" ], - "sha1": "692c5d641d8f57e45695b61eff927a180479f8be", + "sha1": "e4665c506aad21e4dcc6a8b7062581abe3bf62a0", "gitDir": "test/corpus/repos/javascript", - "sha2": "12d619232d825562cfd89152d86da01280a8eed7" + "sha2": "6bfa39fdfcb071bc8fb75a5fd05494f69a160100" } ,{ "testCaseDescription": "javascript-subscript-access-assignment-delete-test", @@ -252,7 +242,6 @@ 1, 1 ], - "filepath": "subscript-access-assignment.js", "end": [ 1, 11 @@ -269,9 +258,9 @@ "filePaths": [ "subscript-access-assignment.js" ], - "sha1": "12d619232d825562cfd89152d86da01280a8eed7", + "sha1": "6bfa39fdfcb071bc8fb75a5fd05494f69a160100", "gitDir": "test/corpus/repos/javascript", - "sha2": "0aa3cdadfd12b36dbf42aaef9f2b42edacb16947" + "sha2": "5d2d00d3e46ea666a3a9b5c03696bd67cf6c731e" } ,{ "testCaseDescription": "javascript-subscript-access-assignment-delete-rest-test", @@ -285,7 +274,6 @@ 1, 1 ], - "filepath": "subscript-access-assignment.js", "end": [ 1, 11 @@ -302,7 +290,7 @@ "filePaths": [ "subscript-access-assignment.js" ], - "sha1": "0aa3cdadfd12b36dbf42aaef9f2b42edacb16947", + "sha1": "5d2d00d3e46ea666a3a9b5c03696bd67cf6c731e", "gitDir": "test/corpus/repos/javascript", - "sha2": "70e4311d385e03edb55b7d538def13b2388666a4" + "sha2": "7bc80d411bdd18724ae9d923e005035511ffc430" }] diff --git a/test/corpus/diff-summaries/javascript/subscript-access-string.json b/test/corpus/diff-summaries/javascript/subscript-access-string.json index 05a52b5dc..f90a687be 100644 --- a/test/corpus/diff-summaries/javascript/subscript-access-string.json +++ b/test/corpus/diff-summaries/javascript/subscript-access-string.json @@ -10,7 +10,6 @@ 1, 1 ], - "filepath": "subscript-access-string.js", "end": [ 1, 17 @@ -27,9 +26,9 @@ "filePaths": [ "subscript-access-string.js" ], - "sha1": "83b00b36c23202837381eadc552ae978ef57f0f5", + "sha1": "055309ae7840b70d0f2d4d43ae7d46457f14ab9d", "gitDir": "test/corpus/repos/javascript", - "sha2": "98db878a3ac653da0586d42c12f2cd835dac018d" + "sha2": "3f459d64b1020d0ca06e2f100b75f9f73c494a47" } ,{ "testCaseDescription": "javascript-subscript-access-string-replacement-insert-test", @@ -43,7 +42,6 @@ 1, 1 ], - "filepath": "subscript-access-string.js", "end": [ 1, 23 @@ -60,7 +58,6 @@ 2, 1 ], - "filepath": "subscript-access-string.js", "end": [ 2, 17 @@ -77,9 +74,9 @@ "filePaths": [ "subscript-access-string.js" ], - "sha1": "98db878a3ac653da0586d42c12f2cd835dac018d", + "sha1": "3f459d64b1020d0ca06e2f100b75f9f73c494a47", "gitDir": "test/corpus/repos/javascript", - "sha2": "7157c914db506131bf00b9f5e021841086795f08" + "sha2": "01f74ece7b9229fc2dfd67d4d81dd7fa0c48b6ca" } ,{ "testCaseDescription": "javascript-subscript-access-string-delete-insert-test", @@ -94,7 +91,6 @@ 1, 3 ], - "filepath": "subscript-access-string.js", "end": [ 1, 22 @@ -105,7 +101,6 @@ 1, 3 ], - "filepath": "subscript-access-string.js", "end": [ 1, 16 @@ -123,9 +118,9 @@ "filePaths": [ "subscript-access-string.js" ], - "sha1": "7157c914db506131bf00b9f5e021841086795f08", + "sha1": "01f74ece7b9229fc2dfd67d4d81dd7fa0c48b6ca", "gitDir": "test/corpus/repos/javascript", - "sha2": "4d92b308d5f619a43ed540c904b2b5b10b5c9329" + "sha2": "44e5b5a6ab3131846486eea2f5c9b6fd07cd78f9" } ,{ "testCaseDescription": "javascript-subscript-access-string-replacement-test", @@ -140,7 +135,6 @@ 1, 3 ], - "filepath": "subscript-access-string.js", "end": [ 1, 16 @@ -151,7 +145,6 @@ 1, 3 ], - "filepath": "subscript-access-string.js", "end": [ 1, 22 @@ -169,9 +162,9 @@ "filePaths": [ "subscript-access-string.js" ], - "sha1": "4d92b308d5f619a43ed540c904b2b5b10b5c9329", + "sha1": "44e5b5a6ab3131846486eea2f5c9b6fd07cd78f9", "gitDir": "test/corpus/repos/javascript", - "sha2": "76435805a581ae7a98c4109298389a504ddb2f71" + "sha2": "c0709672fa207a2ceffe8c206b7bd7fa62f47f31" } ,{ "testCaseDescription": "javascript-subscript-access-string-delete-replacement-test", @@ -185,7 +178,6 @@ 1, 1 ], - "filepath": "subscript-access-string.js", "end": [ 1, 23 @@ -202,7 +194,6 @@ 2, 1 ], - "filepath": "subscript-access-string.js", "end": [ 2, 17 @@ -219,7 +210,6 @@ 2, 1 ], - "filepath": "subscript-access-string.js", "end": [ 2, 23 @@ -236,9 +226,9 @@ "filePaths": [ "subscript-access-string.js" ], - "sha1": "76435805a581ae7a98c4109298389a504ddb2f71", + "sha1": "c0709672fa207a2ceffe8c206b7bd7fa62f47f31", "gitDir": "test/corpus/repos/javascript", - "sha2": "6a6298a6ceee01779c8d39559606bbb70b75e334" + "sha2": "1b7e1b1f1f8ceb744c0dd33891f3450b959244ec" } ,{ "testCaseDescription": "javascript-subscript-access-string-delete-test", @@ -252,7 +242,6 @@ 1, 1 ], - "filepath": "subscript-access-string.js", "end": [ 1, 17 @@ -269,9 +258,9 @@ "filePaths": [ "subscript-access-string.js" ], - "sha1": "6a6298a6ceee01779c8d39559606bbb70b75e334", + "sha1": "1b7e1b1f1f8ceb744c0dd33891f3450b959244ec", "gitDir": "test/corpus/repos/javascript", - "sha2": "dae22c7e845f3b1caa5090199b95ff0987e246ca" + "sha2": "e20ee48f0142390f566a98632a95bd2b359d6ee9" } ,{ "testCaseDescription": "javascript-subscript-access-string-delete-rest-test", @@ -285,7 +274,6 @@ 1, 1 ], - "filepath": "subscript-access-string.js", "end": [ 1, 23 @@ -302,7 +290,7 @@ "filePaths": [ "subscript-access-string.js" ], - "sha1": "dae22c7e845f3b1caa5090199b95ff0987e246ca", + "sha1": "e20ee48f0142390f566a98632a95bd2b359d6ee9", "gitDir": "test/corpus/repos/javascript", - "sha2": "80490123a60bcb2826ae89e9baaba5b8b9517e14" + "sha2": "14ac6caff6e171f4fac4e19d763b702382e888f0" }] diff --git a/test/corpus/diff-summaries/javascript/subscript-access-variable.json b/test/corpus/diff-summaries/javascript/subscript-access-variable.json index 5e1feb342..5f19bce25 100644 --- a/test/corpus/diff-summaries/javascript/subscript-access-variable.json +++ b/test/corpus/diff-summaries/javascript/subscript-access-variable.json @@ -10,7 +10,6 @@ 1, 1 ], - "filepath": "subscript-access-variable.js", "end": [ 1, 16 @@ -27,9 +26,9 @@ "filePaths": [ "subscript-access-variable.js" ], - "sha1": "559c6157818131001576dffc43aefab616ea53e2", + "sha1": "df2335a693daaeb905d9cefae31682611df78425", "gitDir": "test/corpus/repos/javascript", - "sha2": "3a31bb316fc3f7cd51d7983e18e618397842d2c0" + "sha2": "52bab682e3cf604bcd61e8caaa224d7ef8a86e68" } ,{ "testCaseDescription": "javascript-subscript-access-variable-replacement-insert-test", @@ -43,7 +42,6 @@ 1, 1 ], - "filepath": "subscript-access-variable.js", "end": [ 1, 21 @@ -60,7 +58,6 @@ 2, 1 ], - "filepath": "subscript-access-variable.js", "end": [ 2, 16 @@ -77,9 +74,9 @@ "filePaths": [ "subscript-access-variable.js" ], - "sha1": "3a31bb316fc3f7cd51d7983e18e618397842d2c0", + "sha1": "52bab682e3cf604bcd61e8caaa224d7ef8a86e68", "gitDir": "test/corpus/repos/javascript", - "sha2": "b0b94cd0accf04b33000d705358c25fae4b51f86" + "sha2": "01e3f51dfa5b83ed2f37105cc7360e3eca5316a6" } ,{ "testCaseDescription": "javascript-subscript-access-variable-delete-insert-test", @@ -94,7 +91,6 @@ 1, 3 ], - "filepath": "subscript-access-variable.js", "end": [ 1, 20 @@ -105,7 +101,6 @@ 1, 3 ], - "filepath": "subscript-access-variable.js", "end": [ 1, 15 @@ -123,9 +118,9 @@ "filePaths": [ "subscript-access-variable.js" ], - "sha1": "b0b94cd0accf04b33000d705358c25fae4b51f86", + "sha1": "01e3f51dfa5b83ed2f37105cc7360e3eca5316a6", "gitDir": "test/corpus/repos/javascript", - "sha2": "d0f79c7b167b25e0557023dee05e6f08ac374e0e" + "sha2": "38aec4dba28e276cc9993f4e333b8f3a5083ccdc" } ,{ "testCaseDescription": "javascript-subscript-access-variable-replacement-test", @@ -140,7 +135,6 @@ 1, 3 ], - "filepath": "subscript-access-variable.js", "end": [ 1, 15 @@ -151,7 +145,6 @@ 1, 3 ], - "filepath": "subscript-access-variable.js", "end": [ 1, 20 @@ -169,9 +162,9 @@ "filePaths": [ "subscript-access-variable.js" ], - "sha1": "d0f79c7b167b25e0557023dee05e6f08ac374e0e", + "sha1": "38aec4dba28e276cc9993f4e333b8f3a5083ccdc", "gitDir": "test/corpus/repos/javascript", - "sha2": "db72df41f5251046b5b2545e98241a07955d19f4" + "sha2": "8117127e7003788daf170172249a9e3aa7017d65" } ,{ "testCaseDescription": "javascript-subscript-access-variable-delete-replacement-test", @@ -185,7 +178,6 @@ 1, 1 ], - "filepath": "subscript-access-variable.js", "end": [ 1, 21 @@ -202,7 +194,6 @@ 2, 1 ], - "filepath": "subscript-access-variable.js", "end": [ 2, 16 @@ -219,7 +210,6 @@ 2, 1 ], - "filepath": "subscript-access-variable.js", "end": [ 2, 21 @@ -236,9 +226,9 @@ "filePaths": [ "subscript-access-variable.js" ], - "sha1": "db72df41f5251046b5b2545e98241a07955d19f4", + "sha1": "8117127e7003788daf170172249a9e3aa7017d65", "gitDir": "test/corpus/repos/javascript", - "sha2": "c3c3710593bed5c01e614163d6529293655fab16" + "sha2": "797904d3a94beb332c011c660c738e2715d89065" } ,{ "testCaseDescription": "javascript-subscript-access-variable-delete-test", @@ -252,7 +242,6 @@ 1, 1 ], - "filepath": "subscript-access-variable.js", "end": [ 1, 16 @@ -269,9 +258,9 @@ "filePaths": [ "subscript-access-variable.js" ], - "sha1": "c3c3710593bed5c01e614163d6529293655fab16", + "sha1": "797904d3a94beb332c011c660c738e2715d89065", "gitDir": "test/corpus/repos/javascript", - "sha2": "9fd084881a40e1487bae956f71c0ce8f5a56aef5" + "sha2": "f20978a2f5d640425cabb0269559ffc12d458b10" } ,{ "testCaseDescription": "javascript-subscript-access-variable-delete-rest-test", @@ -285,7 +274,6 @@ 1, 1 ], - "filepath": "subscript-access-variable.js", "end": [ 1, 21 @@ -302,7 +290,7 @@ "filePaths": [ "subscript-access-variable.js" ], - "sha1": "9fd084881a40e1487bae956f71c0ce8f5a56aef5", + "sha1": "f20978a2f5d640425cabb0269559ffc12d458b10", "gitDir": "test/corpus/repos/javascript", - "sha2": "83b00b36c23202837381eadc552ae978ef57f0f5" + "sha2": "0bc2b022a5e932ce5bf00c8ebc18b4facc9c1920" }] diff --git a/test/corpus/diff-summaries/javascript/switch-statement.json b/test/corpus/diff-summaries/javascript/switch-statement.json index 5e9e691d6..2991969d1 100644 --- a/test/corpus/diff-summaries/javascript/switch-statement.json +++ b/test/corpus/diff-summaries/javascript/switch-statement.json @@ -10,7 +10,6 @@ 1, 1 ], - "filepath": "switch-statement.js", "end": [ 1, 48 @@ -27,9 +26,9 @@ "filePaths": [ "switch-statement.js" ], - "sha1": "bfb8c510e7246eadb01815b4ede83df2539e0444", + "sha1": "185540018fb2ec8f53780e07b2dfbf4a2f1236e3", "gitDir": "test/corpus/repos/javascript", - "sha2": "cffd698ffab376418fd7e98dcb8f212bf779c152" + "sha2": "e7f419c35bf0a7ee9762ed82ccc1f2186c76ae73" } ,{ "testCaseDescription": "javascript-switch-statement-replacement-insert-test", @@ -43,7 +42,6 @@ 1, 1 ], - "filepath": "switch-statement.js", "end": [ 1, 48 @@ -60,7 +58,6 @@ 2, 1 ], - "filepath": "switch-statement.js", "end": [ 2, 48 @@ -77,9 +74,9 @@ "filePaths": [ "switch-statement.js" ], - "sha1": "cffd698ffab376418fd7e98dcb8f212bf779c152", + "sha1": "e7f419c35bf0a7ee9762ed82ccc1f2186c76ae73", "gitDir": "test/corpus/repos/javascript", - "sha2": "fe0a5807950f18111371be832bff615aaf4771e1" + "sha2": "d64d1ff1bfae7d772398045eb64f6af967f9e873" } ,{ "testCaseDescription": "javascript-switch-statement-delete-insert-test", @@ -94,7 +91,6 @@ 1, 9 ], - "filepath": "switch-statement.js", "end": [ 1, 10 @@ -105,7 +101,6 @@ 1, 9 ], - "filepath": "switch-statement.js", "end": [ 1, 10 @@ -124,7 +119,6 @@ 1, 33 ], - "filepath": "switch-statement.js", "end": [ 1, 34 @@ -135,7 +129,6 @@ 1, 33 ], - "filepath": "switch-statement.js", "end": [ 1, 34 @@ -153,9 +146,9 @@ "filePaths": [ "switch-statement.js" ], - "sha1": "fe0a5807950f18111371be832bff615aaf4771e1", + "sha1": "d64d1ff1bfae7d772398045eb64f6af967f9e873", "gitDir": "test/corpus/repos/javascript", - "sha2": "5cb6917d7e0e3c4adf78440881e9af1ff6487bfe" + "sha2": "6115f065ab997428c6bccc9e5127b10bc064878b" } ,{ "testCaseDescription": "javascript-switch-statement-replacement-test", @@ -170,7 +163,6 @@ 1, 9 ], - "filepath": "switch-statement.js", "end": [ 1, 10 @@ -181,7 +173,6 @@ 1, 9 ], - "filepath": "switch-statement.js", "end": [ 1, 10 @@ -200,7 +191,6 @@ 1, 33 ], - "filepath": "switch-statement.js", "end": [ 1, 34 @@ -211,7 +201,6 @@ 1, 33 ], - "filepath": "switch-statement.js", "end": [ 1, 34 @@ -229,9 +218,9 @@ "filePaths": [ "switch-statement.js" ], - "sha1": "5cb6917d7e0e3c4adf78440881e9af1ff6487bfe", + "sha1": "6115f065ab997428c6bccc9e5127b10bc064878b", "gitDir": "test/corpus/repos/javascript", - "sha2": "0270644f5d84b63561dd236148524c7f5fe50c16" + "sha2": "fe697bb20735d00750474bb1c1d11cf7de7d5584" } ,{ "testCaseDescription": "javascript-switch-statement-delete-replacement-test", @@ -245,7 +234,6 @@ 1, 1 ], - "filepath": "switch-statement.js", "end": [ 1, 48 @@ -262,7 +250,6 @@ 2, 1 ], - "filepath": "switch-statement.js", "end": [ 2, 48 @@ -279,7 +266,6 @@ 2, 1 ], - "filepath": "switch-statement.js", "end": [ 2, 48 @@ -296,9 +282,9 @@ "filePaths": [ "switch-statement.js" ], - "sha1": "0270644f5d84b63561dd236148524c7f5fe50c16", + "sha1": "fe697bb20735d00750474bb1c1d11cf7de7d5584", "gitDir": "test/corpus/repos/javascript", - "sha2": "acbbc8dc48d1a9219c65cb184643745ac0e809db" + "sha2": "a526798e6a2479b18ad0c9e44f6e9ccc22123a0d" } ,{ "testCaseDescription": "javascript-switch-statement-delete-test", @@ -312,7 +298,6 @@ 1, 1 ], - "filepath": "switch-statement.js", "end": [ 1, 48 @@ -329,9 +314,9 @@ "filePaths": [ "switch-statement.js" ], - "sha1": "acbbc8dc48d1a9219c65cb184643745ac0e809db", + "sha1": "a526798e6a2479b18ad0c9e44f6e9ccc22123a0d", "gitDir": "test/corpus/repos/javascript", - "sha2": "b896aeece3867da6d71c11f6191b958b6f876b1c" + "sha2": "6b094744d7e483c03d2bf75a86ae72d45045fe5a" } ,{ "testCaseDescription": "javascript-switch-statement-delete-rest-test", @@ -345,7 +330,6 @@ 1, 1 ], - "filepath": "switch-statement.js", "end": [ 1, 48 @@ -362,7 +346,7 @@ "filePaths": [ "switch-statement.js" ], - "sha1": "b896aeece3867da6d71c11f6191b958b6f876b1c", + "sha1": "6b094744d7e483c03d2bf75a86ae72d45045fe5a", "gitDir": "test/corpus/repos/javascript", - "sha2": "87ee63679cf89692a390eb921ae462b11b4a06e0" + "sha2": "70cb9ad4daaaabe8cba879105f1fa77141f6fa7c" }] diff --git a/test/corpus/diff-summaries/javascript/template-string.json b/test/corpus/diff-summaries/javascript/template-string.json index 4d6f01a7f..c2a1514e6 100644 --- a/test/corpus/diff-summaries/javascript/template-string.json +++ b/test/corpus/diff-summaries/javascript/template-string.json @@ -10,7 +10,6 @@ 1, 1 ], - "filepath": "template-string.js", "end": [ 1, 11 @@ -27,9 +26,9 @@ "filePaths": [ "template-string.js" ], - "sha1": "5e0220ed7ac30b0db50a637fd48230ca14da8570", + "sha1": "d4e864dd49194a81638843e841ec695be0760a6d", "gitDir": "test/corpus/repos/javascript", - "sha2": "d98871e92febc329462bedc8c688840cd259b849" + "sha2": "0d94ff9667630ffc860f5cb5333f5f26852ae555" } ,{ "testCaseDescription": "javascript-template-string-replacement-insert-test", @@ -43,7 +42,6 @@ 1, 1 ], - "filepath": "template-string.js", "end": [ 1, 13 @@ -60,7 +58,6 @@ 2, 1 ], - "filepath": "template-string.js", "end": [ 2, 11 @@ -77,9 +74,9 @@ "filePaths": [ "template-string.js" ], - "sha1": "d98871e92febc329462bedc8c688840cd259b849", + "sha1": "0d94ff9667630ffc860f5cb5333f5f26852ae555", "gitDir": "test/corpus/repos/javascript", - "sha2": "d67750ecf5b9269bbc3761c93b5c94eae1023f48" + "sha2": "72faa91275c8937b1126145609c84a63ab46fbae" } ,{ "testCaseDescription": "javascript-template-string-delete-insert-test", @@ -94,7 +91,6 @@ 1, 1 ], - "filepath": "template-string.js", "end": [ 1, 13 @@ -105,7 +101,6 @@ 1, 1 ], - "filepath": "template-string.js", "end": [ 1, 11 @@ -123,9 +118,9 @@ "filePaths": [ "template-string.js" ], - "sha1": "d67750ecf5b9269bbc3761c93b5c94eae1023f48", + "sha1": "72faa91275c8937b1126145609c84a63ab46fbae", "gitDir": "test/corpus/repos/javascript", - "sha2": "08d7aeef769e43372e65c79fa7df7b7875d9e16f" + "sha2": "db2725ffb5682a26cd55df80bd00aec08cbd0a43" } ,{ "testCaseDescription": "javascript-template-string-replacement-test", @@ -140,7 +135,6 @@ 1, 1 ], - "filepath": "template-string.js", "end": [ 1, 11 @@ -151,7 +145,6 @@ 1, 1 ], - "filepath": "template-string.js", "end": [ 1, 13 @@ -169,9 +162,9 @@ "filePaths": [ "template-string.js" ], - "sha1": "08d7aeef769e43372e65c79fa7df7b7875d9e16f", + "sha1": "db2725ffb5682a26cd55df80bd00aec08cbd0a43", "gitDir": "test/corpus/repos/javascript", - "sha2": "7a66036cf1dc2d97b8768216a05eff379a082bc0" + "sha2": "90298bc75cf5d9c6227abf73fad97faae4e47c59" } ,{ "testCaseDescription": "javascript-template-string-delete-replacement-test", @@ -185,7 +178,6 @@ 1, 1 ], - "filepath": "template-string.js", "end": [ 1, 13 @@ -202,7 +194,6 @@ 2, 1 ], - "filepath": "template-string.js", "end": [ 2, 11 @@ -219,7 +210,6 @@ 2, 1 ], - "filepath": "template-string.js", "end": [ 2, 13 @@ -236,9 +226,9 @@ "filePaths": [ "template-string.js" ], - "sha1": "7a66036cf1dc2d97b8768216a05eff379a082bc0", + "sha1": "90298bc75cf5d9c6227abf73fad97faae4e47c59", "gitDir": "test/corpus/repos/javascript", - "sha2": "cfcad838fe06df4b8d40bbf9b52d4d83d7dda07c" + "sha2": "8769cac2a58027e4e04e72860fa8d37db5752dac" } ,{ "testCaseDescription": "javascript-template-string-delete-test", @@ -252,7 +242,6 @@ 1, 1 ], - "filepath": "template-string.js", "end": [ 1, 11 @@ -269,9 +258,9 @@ "filePaths": [ "template-string.js" ], - "sha1": "cfcad838fe06df4b8d40bbf9b52d4d83d7dda07c", + "sha1": "8769cac2a58027e4e04e72860fa8d37db5752dac", "gitDir": "test/corpus/repos/javascript", - "sha2": "de8088ab3587f3bd19611beaf5bfd61f981c2d1e" + "sha2": "7e0fb2d00a7df954f0b8f7c8ec3f5473fa04df97" } ,{ "testCaseDescription": "javascript-template-string-delete-rest-test", @@ -285,7 +274,6 @@ 1, 1 ], - "filepath": "template-string.js", "end": [ 1, 13 @@ -302,7 +290,7 @@ "filePaths": [ "template-string.js" ], - "sha1": "de8088ab3587f3bd19611beaf5bfd61f981c2d1e", + "sha1": "7e0fb2d00a7df954f0b8f7c8ec3f5473fa04df97", "gitDir": "test/corpus/repos/javascript", - "sha2": "e9fcb09c83fad74eddeca9ca622366a53a55888b" + "sha2": "85d810a0c973ca0394d96cd18baacac324ce884f" }] diff --git a/test/corpus/diff-summaries/javascript/ternary.json b/test/corpus/diff-summaries/javascript/ternary.json index c3598a7a2..754e9e8cb 100644 --- a/test/corpus/diff-summaries/javascript/ternary.json +++ b/test/corpus/diff-summaries/javascript/ternary.json @@ -10,7 +10,6 @@ 1, 1 ], - "filepath": "ternary.js", "end": [ 1, 26 @@ -27,9 +26,9 @@ "filePaths": [ "ternary.js" ], - "sha1": "dd182ba0e84ee13e2e979b15165cf1fe015755e7", + "sha1": "35ef6a37614f71575ccfb227aa8e9984c3b6d87c", "gitDir": "test/corpus/repos/javascript", - "sha2": "cf18bbc39f5339e943551f34d8949c5784cded2c" + "sha2": "0f779997d2c8ddaf9eb3c0c24d0ecd4416e5b353" } ,{ "testCaseDescription": "javascript-ternary-replacement-insert-test", @@ -43,7 +42,6 @@ 1, 1 ], - "filepath": "ternary.js", "end": [ 1, 51 @@ -60,7 +58,6 @@ 2, 1 ], - "filepath": "ternary.js", "end": [ 2, 26 @@ -77,9 +74,9 @@ "filePaths": [ "ternary.js" ], - "sha1": "cf18bbc39f5339e943551f34d8949c5784cded2c", + "sha1": "0f779997d2c8ddaf9eb3c0c24d0ecd4416e5b353", "gitDir": "test/corpus/repos/javascript", - "sha2": "7d4e1911d612358e97882d62f3b42372690d711b" + "sha2": "f3a901fb98a9e4443742c1502d154227c1e29be5" } ,{ "testCaseDescription": "javascript-ternary-delete-insert-test", @@ -93,7 +90,6 @@ 1, 1 ], - "filepath": "ternary.js", "end": [ 1, 26 @@ -110,7 +106,6 @@ 1, 1 ], - "filepath": "ternary.js", "end": [ 1, 51 @@ -127,9 +122,9 @@ "filePaths": [ "ternary.js" ], - "sha1": "7d4e1911d612358e97882d62f3b42372690d711b", + "sha1": "f3a901fb98a9e4443742c1502d154227c1e29be5", "gitDir": "test/corpus/repos/javascript", - "sha2": "97888b680c9d4a6255f18c2b77759729fb053347" + "sha2": "5f6d7b254553b22a73010e4d353197a09b929238" } ,{ "testCaseDescription": "javascript-ternary-replacement-test", @@ -143,7 +138,6 @@ 1, 1 ], - "filepath": "ternary.js", "end": [ 1, 51 @@ -160,7 +154,6 @@ 1, 1 ], - "filepath": "ternary.js", "end": [ 1, 26 @@ -177,9 +170,9 @@ "filePaths": [ "ternary.js" ], - "sha1": "97888b680c9d4a6255f18c2b77759729fb053347", + "sha1": "5f6d7b254553b22a73010e4d353197a09b929238", "gitDir": "test/corpus/repos/javascript", - "sha2": "339185f1b01b822f8875a8b9fa6e23206b083291" + "sha2": "ad6319a0f7acc94d32e996cae0981e1e40bcf7d1" } ,{ "testCaseDescription": "javascript-ternary-delete-replacement-test", @@ -193,7 +186,6 @@ 1, 1 ], - "filepath": "ternary.js", "end": [ 1, 51 @@ -210,7 +202,6 @@ 2, 1 ], - "filepath": "ternary.js", "end": [ 2, 26 @@ -227,7 +218,6 @@ 2, 1 ], - "filepath": "ternary.js", "end": [ 2, 51 @@ -244,9 +234,9 @@ "filePaths": [ "ternary.js" ], - "sha1": "339185f1b01b822f8875a8b9fa6e23206b083291", + "sha1": "ad6319a0f7acc94d32e996cae0981e1e40bcf7d1", "gitDir": "test/corpus/repos/javascript", - "sha2": "28f46d54171719043c974dce30142ba3ae1a7da0" + "sha2": "ee87ff1df9fe1e63ee1afcda1d4922dc732036c3" } ,{ "testCaseDescription": "javascript-ternary-delete-test", @@ -260,7 +250,6 @@ 1, 1 ], - "filepath": "ternary.js", "end": [ 1, 26 @@ -277,9 +266,9 @@ "filePaths": [ "ternary.js" ], - "sha1": "28f46d54171719043c974dce30142ba3ae1a7da0", + "sha1": "ee87ff1df9fe1e63ee1afcda1d4922dc732036c3", "gitDir": "test/corpus/repos/javascript", - "sha2": "bc2351fd9737253c4577435f2116eff8e46bd21e" + "sha2": "d38b443c92e9a74d094943d3ee1893f57a075a30" } ,{ "testCaseDescription": "javascript-ternary-delete-rest-test", @@ -293,7 +282,6 @@ 1, 1 ], - "filepath": "ternary.js", "end": [ 1, 51 @@ -310,7 +298,7 @@ "filePaths": [ "ternary.js" ], - "sha1": "bc2351fd9737253c4577435f2116eff8e46bd21e", + "sha1": "d38b443c92e9a74d094943d3ee1893f57a075a30", "gitDir": "test/corpus/repos/javascript", - "sha2": "36d39106df17e7d991fd60224e3c0189505fe9a7" + "sha2": "d66448c6fbbdc40a36b1c5f8b505ba85856567c5" }] diff --git a/test/corpus/diff-summaries/javascript/this-expression.json b/test/corpus/diff-summaries/javascript/this-expression.json index 03f30eb85..68b6fe959 100644 --- a/test/corpus/diff-summaries/javascript/this-expression.json +++ b/test/corpus/diff-summaries/javascript/this-expression.json @@ -10,7 +10,6 @@ 1, 1 ], - "filepath": "this-expression.js", "end": [ 1, 5 @@ -27,9 +26,9 @@ "filePaths": [ "this-expression.js" ], - "sha1": "a0b31feb22c899b106e153d1abbe125b102e7ddb", + "sha1": "7b97e72d7c0e6b3898be9d1deb06da6b7ea09764", "gitDir": "test/corpus/repos/javascript", - "sha2": "753cb180424907bbe0888abdc02a401f46ef4ce4" + "sha2": "a2a8fb25467bf9403e4de37a8f434852ed8f848b" } ,{ "testCaseDescription": "javascript-this-expression-replacement-insert-test", @@ -43,7 +42,6 @@ 1, 1 ], - "filepath": "this-expression.js", "end": [ 1, 13 @@ -60,7 +58,6 @@ 2, 1 ], - "filepath": "this-expression.js", "end": [ 2, 5 @@ -77,9 +74,9 @@ "filePaths": [ "this-expression.js" ], - "sha1": "753cb180424907bbe0888abdc02a401f46ef4ce4", + "sha1": "a2a8fb25467bf9403e4de37a8f434852ed8f848b", "gitDir": "test/corpus/repos/javascript", - "sha2": "654307c95dc0c80c6a5233c515c3ccc417c5b8dd" + "sha2": "6625c63c5f06e702ef97f2fdc3a25ff525e70e4f" } ,{ "testCaseDescription": "javascript-this-expression-delete-insert-test", @@ -93,7 +90,6 @@ 1, 1 ], - "filepath": "this-expression.js", "end": [ 1, 5 @@ -110,7 +106,6 @@ 1, 1 ], - "filepath": "this-expression.js", "end": [ 1, 13 @@ -127,9 +122,9 @@ "filePaths": [ "this-expression.js" ], - "sha1": "654307c95dc0c80c6a5233c515c3ccc417c5b8dd", + "sha1": "6625c63c5f06e702ef97f2fdc3a25ff525e70e4f", "gitDir": "test/corpus/repos/javascript", - "sha2": "c8908ed9d5b7f834e930ca5af7efa45daaa9140b" + "sha2": "ffbed3418a24653fbd26b4cd35deb23988f30198" } ,{ "testCaseDescription": "javascript-this-expression-replacement-test", @@ -143,7 +138,6 @@ 1, 1 ], - "filepath": "this-expression.js", "end": [ 1, 13 @@ -160,7 +154,6 @@ 1, 1 ], - "filepath": "this-expression.js", "end": [ 1, 5 @@ -177,9 +170,9 @@ "filePaths": [ "this-expression.js" ], - "sha1": "c8908ed9d5b7f834e930ca5af7efa45daaa9140b", + "sha1": "ffbed3418a24653fbd26b4cd35deb23988f30198", "gitDir": "test/corpus/repos/javascript", - "sha2": "1119408a872e348a53b96c9cb58ce45ae9644581" + "sha2": "7db7900eb04a66af0196e73999687ba83b168947" } ,{ "testCaseDescription": "javascript-this-expression-delete-replacement-test", @@ -193,7 +186,6 @@ 1, 1 ], - "filepath": "this-expression.js", "end": [ 1, 13 @@ -210,7 +202,6 @@ 2, 1 ], - "filepath": "this-expression.js", "end": [ 2, 5 @@ -227,7 +218,6 @@ 2, 1 ], - "filepath": "this-expression.js", "end": [ 2, 13 @@ -244,9 +234,9 @@ "filePaths": [ "this-expression.js" ], - "sha1": "1119408a872e348a53b96c9cb58ce45ae9644581", + "sha1": "7db7900eb04a66af0196e73999687ba83b168947", "gitDir": "test/corpus/repos/javascript", - "sha2": "1425f90993e565bc6d65d94cad9827980243879b" + "sha2": "220159fc73518eb2ba3c195c9d230c523137fb9d" } ,{ "testCaseDescription": "javascript-this-expression-delete-test", @@ -260,7 +250,6 @@ 1, 1 ], - "filepath": "this-expression.js", "end": [ 1, 5 @@ -277,9 +266,9 @@ "filePaths": [ "this-expression.js" ], - "sha1": "1425f90993e565bc6d65d94cad9827980243879b", + "sha1": "220159fc73518eb2ba3c195c9d230c523137fb9d", "gitDir": "test/corpus/repos/javascript", - "sha2": "b41ef9cf7c33890dcf4b8af86f5cfe3b760467d3" + "sha2": "3594ddd1cbf054031d468b2ce85d2c617ac5bd51" } ,{ "testCaseDescription": "javascript-this-expression-delete-rest-test", @@ -293,7 +282,6 @@ 1, 1 ], - "filepath": "this-expression.js", "end": [ 1, 13 @@ -310,7 +298,7 @@ "filePaths": [ "this-expression.js" ], - "sha1": "b41ef9cf7c33890dcf4b8af86f5cfe3b760467d3", + "sha1": "3594ddd1cbf054031d468b2ce85d2c617ac5bd51", "gitDir": "test/corpus/repos/javascript", - "sha2": "0778d978feeb2e6973ff377ef502edef0f0ad001" + "sha2": "72aab09a49d2096eccd1ff0f785ef1b2d9283961" }] diff --git a/test/corpus/diff-summaries/javascript/throw-statement.json b/test/corpus/diff-summaries/javascript/throw-statement.json index 5b346943c..aee57f66a 100644 --- a/test/corpus/diff-summaries/javascript/throw-statement.json +++ b/test/corpus/diff-summaries/javascript/throw-statement.json @@ -10,7 +10,6 @@ 1, 1 ], - "filepath": "throw-statement.js", "end": [ 1, 26 @@ -27,9 +26,9 @@ "filePaths": [ "throw-statement.js" ], - "sha1": "87ee63679cf89692a390eb921ae462b11b4a06e0", + "sha1": "4703a7002d32db2234780ed17ed8bf95a45569ca", "gitDir": "test/corpus/repos/javascript", - "sha2": "f14dd81890ac415d276801c1571ae13d4ddc96af" + "sha2": "2518b94568794c2a248421a57291d345fc132b7f" } ,{ "testCaseDescription": "javascript-throw-statement-replacement-insert-test", @@ -43,7 +42,6 @@ 1, 1 ], - "filepath": "throw-statement.js", "end": [ 1, 29 @@ -60,7 +58,6 @@ 2, 1 ], - "filepath": "throw-statement.js", "end": [ 2, 26 @@ -77,9 +74,9 @@ "filePaths": [ "throw-statement.js" ], - "sha1": "f14dd81890ac415d276801c1571ae13d4ddc96af", + "sha1": "2518b94568794c2a248421a57291d345fc132b7f", "gitDir": "test/corpus/repos/javascript", - "sha2": "f40e06699f4c62cbe28402a49217a50745d4951a" + "sha2": "18284196ba4ca0689123160a21accbfc055487bb" } ,{ "testCaseDescription": "javascript-throw-statement-delete-insert-test", @@ -94,7 +91,6 @@ 1, 17 ], - "filepath": "throw-statement.js", "end": [ 1, 27 @@ -105,7 +101,6 @@ 1, 17 ], - "filepath": "throw-statement.js", "end": [ 1, 24 @@ -123,9 +118,9 @@ "filePaths": [ "throw-statement.js" ], - "sha1": "f40e06699f4c62cbe28402a49217a50745d4951a", + "sha1": "18284196ba4ca0689123160a21accbfc055487bb", "gitDir": "test/corpus/repos/javascript", - "sha2": "e419aef46115c692e1dce0182e889d147bab900b" + "sha2": "1de92de9bdc5fa85de0e9b5b5dc5c23590ac2566" } ,{ "testCaseDescription": "javascript-throw-statement-replacement-test", @@ -140,7 +135,6 @@ 1, 17 ], - "filepath": "throw-statement.js", "end": [ 1, 24 @@ -151,7 +145,6 @@ 1, 17 ], - "filepath": "throw-statement.js", "end": [ 1, 27 @@ -169,9 +162,9 @@ "filePaths": [ "throw-statement.js" ], - "sha1": "e419aef46115c692e1dce0182e889d147bab900b", + "sha1": "1de92de9bdc5fa85de0e9b5b5dc5c23590ac2566", "gitDir": "test/corpus/repos/javascript", - "sha2": "456b9d703a0897c3ae7ffcccb88b633d24d6e772" + "sha2": "d48e3de54842bdfb75cd8abeb4cebdcd43b877a4" } ,{ "testCaseDescription": "javascript-throw-statement-delete-replacement-test", @@ -185,7 +178,6 @@ 1, 1 ], - "filepath": "throw-statement.js", "end": [ 1, 29 @@ -202,7 +194,6 @@ 2, 1 ], - "filepath": "throw-statement.js", "end": [ 2, 26 @@ -219,7 +210,6 @@ 2, 1 ], - "filepath": "throw-statement.js", "end": [ 2, 29 @@ -236,9 +226,9 @@ "filePaths": [ "throw-statement.js" ], - "sha1": "456b9d703a0897c3ae7ffcccb88b633d24d6e772", + "sha1": "d48e3de54842bdfb75cd8abeb4cebdcd43b877a4", "gitDir": "test/corpus/repos/javascript", - "sha2": "a0241ec11741dd48f4789522c53554a6c0e51ec5" + "sha2": "7968d5456d2cae631c2ad1a3541972e8b3fbec42" } ,{ "testCaseDescription": "javascript-throw-statement-delete-test", @@ -252,7 +242,6 @@ 1, 1 ], - "filepath": "throw-statement.js", "end": [ 1, 26 @@ -269,9 +258,9 @@ "filePaths": [ "throw-statement.js" ], - "sha1": "a0241ec11741dd48f4789522c53554a6c0e51ec5", + "sha1": "7968d5456d2cae631c2ad1a3541972e8b3fbec42", "gitDir": "test/corpus/repos/javascript", - "sha2": "9f6bb83269360c82b0a7d8f0876db24bec390b09" + "sha2": "b2a674bd06b1fd6701d58556d05daf118bd513fc" } ,{ "testCaseDescription": "javascript-throw-statement-delete-rest-test", @@ -285,7 +274,6 @@ 1, 1 ], - "filepath": "throw-statement.js", "end": [ 1, 29 @@ -302,7 +290,7 @@ "filePaths": [ "throw-statement.js" ], - "sha1": "9f6bb83269360c82b0a7d8f0876db24bec390b09", + "sha1": "b2a674bd06b1fd6701d58556d05daf118bd513fc", "gitDir": "test/corpus/repos/javascript", - "sha2": "5886a80268586c2725f1f8be03d2dea099ba0bd2" + "sha2": "a11797b72e3d4338dc9efc6183177921bc93609e" }] diff --git a/test/corpus/diff-summaries/javascript/true.json b/test/corpus/diff-summaries/javascript/true.json index 3022124a9..c00dba9ae 100644 --- a/test/corpus/diff-summaries/javascript/true.json +++ b/test/corpus/diff-summaries/javascript/true.json @@ -10,7 +10,6 @@ 1, 1 ], - "filepath": "true.js", "end": [ 1, 5 @@ -27,9 +26,9 @@ "filePaths": [ "true.js" ], - "sha1": "824ee002efef5456f35f7ccf48e0991891cafc57", + "sha1": "e8bb54ef7035c6f0ab215c7f0af3134871bd2d37", "gitDir": "test/corpus/repos/javascript", - "sha2": "80ec45b5c5be7b6580cf6335811a63e0678f5d76" + "sha2": "95ae5cef054c9d3c1a77535d0fd7b9261b13aeb9" } ,{ "testCaseDescription": "javascript-true-replacement-insert-test", @@ -43,7 +42,6 @@ 1, 1 ], - "filepath": "true.js", "end": [ 1, 13 @@ -60,7 +58,6 @@ 2, 1 ], - "filepath": "true.js", "end": [ 2, 5 @@ -77,9 +74,9 @@ "filePaths": [ "true.js" ], - "sha1": "80ec45b5c5be7b6580cf6335811a63e0678f5d76", + "sha1": "95ae5cef054c9d3c1a77535d0fd7b9261b13aeb9", "gitDir": "test/corpus/repos/javascript", - "sha2": "023fb246c0d4434e5803e4d2146fa347b66f1898" + "sha2": "81f477d087ea9dc02376766508a16e7f01c4bcc3" } ,{ "testCaseDescription": "javascript-true-delete-insert-test", @@ -93,7 +90,6 @@ 1, 1 ], - "filepath": "true.js", "end": [ 1, 5 @@ -110,7 +106,6 @@ 1, 1 ], - "filepath": "true.js", "end": [ 1, 13 @@ -127,9 +122,9 @@ "filePaths": [ "true.js" ], - "sha1": "023fb246c0d4434e5803e4d2146fa347b66f1898", + "sha1": "81f477d087ea9dc02376766508a16e7f01c4bcc3", "gitDir": "test/corpus/repos/javascript", - "sha2": "e6f76e586bd9ddb0a235e999eaa57602af8ccb1b" + "sha2": "75e755b738850d3338c31320413ad8696884fe31" } ,{ "testCaseDescription": "javascript-true-replacement-test", @@ -143,7 +138,6 @@ 1, 1 ], - "filepath": "true.js", "end": [ 1, 13 @@ -160,7 +154,6 @@ 1, 1 ], - "filepath": "true.js", "end": [ 1, 5 @@ -177,9 +170,9 @@ "filePaths": [ "true.js" ], - "sha1": "e6f76e586bd9ddb0a235e999eaa57602af8ccb1b", + "sha1": "75e755b738850d3338c31320413ad8696884fe31", "gitDir": "test/corpus/repos/javascript", - "sha2": "f564b8abd977c41082d593c5662ade8d130b14ca" + "sha2": "6d14f16bb963f4554bd80dc780330ffc3dc66ac0" } ,{ "testCaseDescription": "javascript-true-delete-replacement-test", @@ -193,7 +186,6 @@ 1, 1 ], - "filepath": "true.js", "end": [ 1, 13 @@ -210,7 +202,6 @@ 2, 1 ], - "filepath": "true.js", "end": [ 2, 5 @@ -227,7 +218,6 @@ 2, 1 ], - "filepath": "true.js", "end": [ 2, 13 @@ -244,9 +234,9 @@ "filePaths": [ "true.js" ], - "sha1": "f564b8abd977c41082d593c5662ade8d130b14ca", + "sha1": "6d14f16bb963f4554bd80dc780330ffc3dc66ac0", "gitDir": "test/corpus/repos/javascript", - "sha2": "85a35504f36a68bd2118b79afe7931b627597b28" + "sha2": "5ed630e1aab4b6b806751b920fc74d9d05081fb2" } ,{ "testCaseDescription": "javascript-true-delete-test", @@ -260,7 +250,6 @@ 1, 1 ], - "filepath": "true.js", "end": [ 1, 5 @@ -277,9 +266,9 @@ "filePaths": [ "true.js" ], - "sha1": "85a35504f36a68bd2118b79afe7931b627597b28", + "sha1": "5ed630e1aab4b6b806751b920fc74d9d05081fb2", "gitDir": "test/corpus/repos/javascript", - "sha2": "98083e291fb4e869d1327d14e78523f1c966fead" + "sha2": "aced0cd3388a00dec08265c65fabcbdc18195d78" } ,{ "testCaseDescription": "javascript-true-delete-rest-test", @@ -293,7 +282,6 @@ 1, 1 ], - "filepath": "true.js", "end": [ 1, 13 @@ -310,7 +298,7 @@ "filePaths": [ "true.js" ], - "sha1": "98083e291fb4e869d1327d14e78523f1c966fead", + "sha1": "aced0cd3388a00dec08265c65fabcbdc18195d78", "gitDir": "test/corpus/repos/javascript", - "sha2": "4bdbc3b261a181ab8a66d17f1946997d7cf9e70c" + "sha2": "ec94fd01e01d796cac3744f43515ffaad64f1fbf" }] diff --git a/test/corpus/diff-summaries/javascript/try-statement.json b/test/corpus/diff-summaries/javascript/try-statement.json index d6e95a48b..fe8c431e2 100644 --- a/test/corpus/diff-summaries/javascript/try-statement.json +++ b/test/corpus/diff-summaries/javascript/try-statement.json @@ -10,7 +10,6 @@ 1, 1 ], - "filepath": "try-statement.js", "end": [ 1, 39 @@ -27,9 +26,9 @@ "filePaths": [ "try-statement.js" ], - "sha1": "5886a80268586c2725f1f8be03d2dea099ba0bd2", + "sha1": "edf461750d55ec70810d768af2bc471f00736c6f", "gitDir": "test/corpus/repos/javascript", - "sha2": "d11694b9b5ba9a379cc650e52b21506d9f9aa3ba" + "sha2": "dd72da3c12c1af00ba82506f288d1e07e0329005" } ,{ "testCaseDescription": "javascript-try-statement-replacement-insert-test", @@ -43,7 +42,6 @@ 1, 1 ], - "filepath": "try-statement.js", "end": [ 1, 39 @@ -60,7 +58,6 @@ 2, 1 ], - "filepath": "try-statement.js", "end": [ 2, 39 @@ -77,9 +74,9 @@ "filePaths": [ "try-statement.js" ], - "sha1": "d11694b9b5ba9a379cc650e52b21506d9f9aa3ba", + "sha1": "dd72da3c12c1af00ba82506f288d1e07e0329005", "gitDir": "test/corpus/repos/javascript", - "sha2": "82c1948da9d8ea2646160c6264953c6ab2ae0b41" + "sha2": "aef5631ddb1eadeea819782d6cad5ebaa3267263" } ,{ "testCaseDescription": "javascript-try-statement-delete-insert-test", @@ -94,7 +91,6 @@ 1, 20 ], - "filepath": "try-statement.js", "end": [ 1, 21 @@ -105,7 +101,6 @@ 1, 20 ], - "filepath": "try-statement.js", "end": [ 1, 21 @@ -124,7 +119,6 @@ 1, 35 ], - "filepath": "try-statement.js", "end": [ 1, 36 @@ -135,7 +129,6 @@ 1, 35 ], - "filepath": "try-statement.js", "end": [ 1, 36 @@ -153,9 +146,9 @@ "filePaths": [ "try-statement.js" ], - "sha1": "82c1948da9d8ea2646160c6264953c6ab2ae0b41", + "sha1": "aef5631ddb1eadeea819782d6cad5ebaa3267263", "gitDir": "test/corpus/repos/javascript", - "sha2": "6ad2a6b1f0bbe574a911599cf820f54b7e1390d9" + "sha2": "ed026d2a79ed7e2935aa2c6654802265cfd1e277" } ,{ "testCaseDescription": "javascript-try-statement-replacement-test", @@ -170,7 +163,6 @@ 1, 20 ], - "filepath": "try-statement.js", "end": [ 1, 21 @@ -181,7 +173,6 @@ 1, 20 ], - "filepath": "try-statement.js", "end": [ 1, 21 @@ -200,7 +191,6 @@ 1, 35 ], - "filepath": "try-statement.js", "end": [ 1, 36 @@ -211,7 +201,6 @@ 1, 35 ], - "filepath": "try-statement.js", "end": [ 1, 36 @@ -229,9 +218,9 @@ "filePaths": [ "try-statement.js" ], - "sha1": "6ad2a6b1f0bbe574a911599cf820f54b7e1390d9", + "sha1": "ed026d2a79ed7e2935aa2c6654802265cfd1e277", "gitDir": "test/corpus/repos/javascript", - "sha2": "79cd78e2b7db8045abfbeac9a122ce59a20fc740" + "sha2": "7e2d4a57ded708e456a65e74de6aa306f109e7f1" } ,{ "testCaseDescription": "javascript-try-statement-delete-replacement-test", @@ -245,7 +234,6 @@ 1, 1 ], - "filepath": "try-statement.js", "end": [ 1, 39 @@ -262,7 +250,6 @@ 2, 1 ], - "filepath": "try-statement.js", "end": [ 2, 39 @@ -279,7 +266,6 @@ 2, 1 ], - "filepath": "try-statement.js", "end": [ 2, 39 @@ -296,9 +282,9 @@ "filePaths": [ "try-statement.js" ], - "sha1": "79cd78e2b7db8045abfbeac9a122ce59a20fc740", + "sha1": "7e2d4a57ded708e456a65e74de6aa306f109e7f1", "gitDir": "test/corpus/repos/javascript", - "sha2": "c208bceaa74698f28aeaebc6b0bf11b95c3e8454" + "sha2": "a08334179979e507269d2d4d225b43fabdf08231" } ,{ "testCaseDescription": "javascript-try-statement-delete-test", @@ -312,7 +298,6 @@ 1, 1 ], - "filepath": "try-statement.js", "end": [ 1, 39 @@ -329,9 +314,9 @@ "filePaths": [ "try-statement.js" ], - "sha1": "c208bceaa74698f28aeaebc6b0bf11b95c3e8454", + "sha1": "a08334179979e507269d2d4d225b43fabdf08231", "gitDir": "test/corpus/repos/javascript", - "sha2": "ea97f7b13e155e96e812b3555a3b553ef47a10fe" + "sha2": "6375ef5c9ef95bc52a4f4d0b27b25a45ee6d4ad0" } ,{ "testCaseDescription": "javascript-try-statement-delete-rest-test", @@ -345,7 +330,6 @@ 1, 1 ], - "filepath": "try-statement.js", "end": [ 1, 39 @@ -362,7 +346,7 @@ "filePaths": [ "try-statement.js" ], - "sha1": "ea97f7b13e155e96e812b3555a3b553ef47a10fe", + "sha1": "6375ef5c9ef95bc52a4f4d0b27b25a45ee6d4ad0", "gitDir": "test/corpus/repos/javascript", - "sha2": "058fa89622b13938f1d49514c08fc3297f2654b2" + "sha2": "d1920048204583b13ae78843de8cb2aceb164574" }] diff --git a/test/corpus/diff-summaries/javascript/type-operator.json b/test/corpus/diff-summaries/javascript/type-operator.json index 966a5bb92..8b07b8e39 100644 --- a/test/corpus/diff-summaries/javascript/type-operator.json +++ b/test/corpus/diff-summaries/javascript/type-operator.json @@ -10,7 +10,6 @@ 1, 1 ], - "filepath": "type-operator.js", "end": [ 1, 9 @@ -27,9 +26,9 @@ "filePaths": [ "type-operator.js" ], - "sha1": "36d39106df17e7d991fd60224e3c0189505fe9a7", + "sha1": "184d21574db41e0343ee9e0ebe166495b6205fff", "gitDir": "test/corpus/repos/javascript", - "sha2": "f433383cd8dd14593d8a18d0779a49270638a7c9" + "sha2": "720e0e4fb3fd308a3a024852f65dccb5a3159645" } ,{ "testCaseDescription": "javascript-type-operator-replacement-insert-test", @@ -43,7 +42,6 @@ 1, 1 ], - "filepath": "type-operator.js", "end": [ 1, 20 @@ -60,7 +58,6 @@ 2, 1 ], - "filepath": "type-operator.js", "end": [ 2, 9 @@ -77,9 +74,9 @@ "filePaths": [ "type-operator.js" ], - "sha1": "f433383cd8dd14593d8a18d0779a49270638a7c9", + "sha1": "720e0e4fb3fd308a3a024852f65dccb5a3159645", "gitDir": "test/corpus/repos/javascript", - "sha2": "5ec3eddcb180a6def3bf030be54b77050c2b20e6" + "sha2": "ba9af83b00f98272bde1cab0c624397e934650c0" } ,{ "testCaseDescription": "javascript-type-operator-delete-insert-test", @@ -93,7 +90,6 @@ 1, 14 ], - "filepath": "type-operator.js", "end": [ 1, 20 @@ -110,9 +106,9 @@ "filePaths": [ "type-operator.js" ], - "sha1": "5ec3eddcb180a6def3bf030be54b77050c2b20e6", + "sha1": "ba9af83b00f98272bde1cab0c624397e934650c0", "gitDir": "test/corpus/repos/javascript", - "sha2": "b4fd8c7c8da20719c150f97209d8a00a946b47b9" + "sha2": "71d60e89b4137fd4a2e0cc552789f9cfc04264c3" } ,{ "testCaseDescription": "javascript-type-operator-replacement-test", @@ -126,7 +122,6 @@ 1, 14 ], - "filepath": "type-operator.js", "end": [ 1, 20 @@ -143,9 +138,9 @@ "filePaths": [ "type-operator.js" ], - "sha1": "b4fd8c7c8da20719c150f97209d8a00a946b47b9", + "sha1": "71d60e89b4137fd4a2e0cc552789f9cfc04264c3", "gitDir": "test/corpus/repos/javascript", - "sha2": "bd42bc71c775872fa957a75c9c726143e95c581a" + "sha2": "1c735c0485ca5c653addd5814e52595ac5787cdb" } ,{ "testCaseDescription": "javascript-type-operator-delete-replacement-test", @@ -159,7 +154,6 @@ 1, 1 ], - "filepath": "type-operator.js", "end": [ 1, 20 @@ -176,7 +170,6 @@ 2, 1 ], - "filepath": "type-operator.js", "end": [ 2, 9 @@ -193,7 +186,6 @@ 2, 1 ], - "filepath": "type-operator.js", "end": [ 2, 20 @@ -210,9 +202,9 @@ "filePaths": [ "type-operator.js" ], - "sha1": "bd42bc71c775872fa957a75c9c726143e95c581a", + "sha1": "1c735c0485ca5c653addd5814e52595ac5787cdb", "gitDir": "test/corpus/repos/javascript", - "sha2": "561a8e99f9c5a2a2c8e1c0fcbfca58522b922d16" + "sha2": "c85218016394b93295e0cef901de2755be8e901c" } ,{ "testCaseDescription": "javascript-type-operator-delete-test", @@ -226,7 +218,6 @@ 1, 1 ], - "filepath": "type-operator.js", "end": [ 1, 9 @@ -243,9 +234,9 @@ "filePaths": [ "type-operator.js" ], - "sha1": "561a8e99f9c5a2a2c8e1c0fcbfca58522b922d16", + "sha1": "c85218016394b93295e0cef901de2755be8e901c", "gitDir": "test/corpus/repos/javascript", - "sha2": "9df4658d7424a8a103978f23bb2eb6e55219c9ce" + "sha2": "2928891cdd48936b69827f3ae19220bbb30d3b6e" } ,{ "testCaseDescription": "javascript-type-operator-delete-rest-test", @@ -259,7 +250,6 @@ 1, 1 ], - "filepath": "type-operator.js", "end": [ 1, 20 @@ -276,7 +266,7 @@ "filePaths": [ "type-operator.js" ], - "sha1": "9df4658d7424a8a103978f23bb2eb6e55219c9ce", + "sha1": "2928891cdd48936b69827f3ae19220bbb30d3b6e", "gitDir": "test/corpus/repos/javascript", - "sha2": "d7d8b169c8385f3a91f99dd299e5ebb566e5a346" + "sha2": "50c9fb7f60331db7c4a5580663122bf6c875340c" }] diff --git a/test/corpus/diff-summaries/javascript/undefined.json b/test/corpus/diff-summaries/javascript/undefined.json index 935c1973b..129d33729 100644 --- a/test/corpus/diff-summaries/javascript/undefined.json +++ b/test/corpus/diff-summaries/javascript/undefined.json @@ -10,7 +10,6 @@ 1, 1 ], - "filepath": "undefined.js", "end": [ 1, 10 @@ -27,9 +26,9 @@ "filePaths": [ "undefined.js" ], - "sha1": "a73ced91fe252bb89e890167a057a2e445e59bde", + "sha1": "3e883f3c905964aa9c04a836721989934f251368", "gitDir": "test/corpus/repos/javascript", - "sha2": "2f04ff596724d15e73d8a88ac947084c725be725" + "sha2": "24616410c732e4ed0d2bdd366a9b7c65f1350ab9" } ,{ "testCaseDescription": "javascript-undefined-replacement-insert-test", @@ -43,7 +42,6 @@ 1, 1 ], - "filepath": "undefined.js", "end": [ 1, 18 @@ -60,7 +58,6 @@ 2, 1 ], - "filepath": "undefined.js", "end": [ 2, 10 @@ -77,9 +74,9 @@ "filePaths": [ "undefined.js" ], - "sha1": "2f04ff596724d15e73d8a88ac947084c725be725", + "sha1": "24616410c732e4ed0d2bdd366a9b7c65f1350ab9", "gitDir": "test/corpus/repos/javascript", - "sha2": "bfc3de81ee165c8d386d6c109c798b1ebdea4f4f" + "sha2": "65b072d0a6fc020645b06825f6575c2b445e88fe" } ,{ "testCaseDescription": "javascript-undefined-delete-insert-test", @@ -93,7 +90,6 @@ 1, 1 ], - "filepath": "undefined.js", "end": [ 1, 10 @@ -110,7 +106,6 @@ 1, 1 ], - "filepath": "undefined.js", "end": [ 1, 18 @@ -127,9 +122,9 @@ "filePaths": [ "undefined.js" ], - "sha1": "bfc3de81ee165c8d386d6c109c798b1ebdea4f4f", + "sha1": "65b072d0a6fc020645b06825f6575c2b445e88fe", "gitDir": "test/corpus/repos/javascript", - "sha2": "a09bedf22b4121366d93cfb4adaac41de2ebbf4b" + "sha2": "844f980e3cd0425b33d6750fd10f33a7c2e52ad5" } ,{ "testCaseDescription": "javascript-undefined-replacement-test", @@ -143,7 +138,6 @@ 1, 1 ], - "filepath": "undefined.js", "end": [ 1, 18 @@ -160,7 +154,6 @@ 1, 1 ], - "filepath": "undefined.js", "end": [ 1, 10 @@ -177,9 +170,9 @@ "filePaths": [ "undefined.js" ], - "sha1": "a09bedf22b4121366d93cfb4adaac41de2ebbf4b", + "sha1": "844f980e3cd0425b33d6750fd10f33a7c2e52ad5", "gitDir": "test/corpus/repos/javascript", - "sha2": "153996f81f90657fd4c869eae90ed9f5dcb46934" + "sha2": "0908d4dfcb1c0b86f4ca20bd055670ebbe0e9dac" } ,{ "testCaseDescription": "javascript-undefined-delete-replacement-test", @@ -193,7 +186,6 @@ 1, 1 ], - "filepath": "undefined.js", "end": [ 1, 18 @@ -210,7 +202,6 @@ 2, 1 ], - "filepath": "undefined.js", "end": [ 2, 10 @@ -227,7 +218,6 @@ 2, 1 ], - "filepath": "undefined.js", "end": [ 2, 18 @@ -244,9 +234,9 @@ "filePaths": [ "undefined.js" ], - "sha1": "153996f81f90657fd4c869eae90ed9f5dcb46934", + "sha1": "0908d4dfcb1c0b86f4ca20bd055670ebbe0e9dac", "gitDir": "test/corpus/repos/javascript", - "sha2": "042e685e444ebc963aa3486dde11fd69318dfb9a" + "sha2": "3439b9b0f4daba5fb029403dcc7d37d7d5f147de" } ,{ "testCaseDescription": "javascript-undefined-delete-test", @@ -260,7 +250,6 @@ 1, 1 ], - "filepath": "undefined.js", "end": [ 1, 10 @@ -277,9 +266,9 @@ "filePaths": [ "undefined.js" ], - "sha1": "042e685e444ebc963aa3486dde11fd69318dfb9a", + "sha1": "3439b9b0f4daba5fb029403dcc7d37d7d5f147de", "gitDir": "test/corpus/repos/javascript", - "sha2": "2fe9d802d0454f028add54c66529a5cf8fec10ca" + "sha2": "fd6bea53f81c603df1baa77d61048b0c7162d3ed" } ,{ "testCaseDescription": "javascript-undefined-delete-rest-test", @@ -293,7 +282,6 @@ 1, 1 ], - "filepath": "undefined.js", "end": [ 1, 18 @@ -310,7 +298,7 @@ "filePaths": [ "undefined.js" ], - "sha1": "2fe9d802d0454f028add54c66529a5cf8fec10ca", + "sha1": "fd6bea53f81c603df1baa77d61048b0c7162d3ed", "gitDir": "test/corpus/repos/javascript", - "sha2": "824ee002efef5456f35f7ccf48e0991891cafc57" + "sha2": "3e1c52cdcfb175a8271723e1584824e78861caa0" }] diff --git a/test/corpus/diff-summaries/javascript/var-declaration.json b/test/corpus/diff-summaries/javascript/var-declaration.json index a9f1304f8..8efe6415b 100644 --- a/test/corpus/diff-summaries/javascript/var-declaration.json +++ b/test/corpus/diff-summaries/javascript/var-declaration.json @@ -10,7 +10,6 @@ 1, 5 ], - "filepath": "var-declaration.js", "end": [ 1, 10 @@ -27,9 +26,9 @@ "filePaths": [ "var-declaration.js" ], - "sha1": "654be5306d35ca185023c542852d13f395b9233d", + "sha1": "9cb880c6d183e0ff29f5a379bf6bfe8a91ea75f0", "gitDir": "test/corpus/repos/javascript", - "sha2": "dcc848fc01f8bdc29b190973a80f357a23063499" + "sha2": "9be12afcd6174bb4ccbb9e4e203ff9c2ebd05c2f" } ,{ "testCaseDescription": "javascript-var-declaration-replacement-insert-test", @@ -43,7 +42,6 @@ 1, 5 ], - "filepath": "var-declaration.js", "end": [ 1, 6 @@ -60,7 +58,6 @@ 1, 8 ], - "filepath": "var-declaration.js", "end": [ 1, 14 @@ -77,7 +74,6 @@ 1, 16 ], - "filepath": "var-declaration.js", "end": [ 1, 17 @@ -94,7 +90,6 @@ 2, 5 ], - "filepath": "var-declaration.js", "end": [ 2, 10 @@ -111,9 +106,9 @@ "filePaths": [ "var-declaration.js" ], - "sha1": "dcc848fc01f8bdc29b190973a80f357a23063499", + "sha1": "9be12afcd6174bb4ccbb9e4e203ff9c2ebd05c2f", "gitDir": "test/corpus/repos/javascript", - "sha2": "d58f0f3b2772c532d4abfb2617530a019c706fe1" + "sha2": "ed055ea2c0cdae06c2679c7febe33ea291ab50af" } ,{ "testCaseDescription": "javascript-var-declaration-delete-insert-test", @@ -128,7 +123,6 @@ 1, 5 ], - "filepath": "var-declaration.js", "end": [ 1, 6 @@ -139,7 +133,6 @@ 1, 5 ], - "filepath": "var-declaration.js", "end": [ 1, 10 @@ -157,7 +150,6 @@ 1, 8 ], - "filepath": "var-declaration.js", "end": [ 1, 14 @@ -174,7 +166,6 @@ 1, 16 ], - "filepath": "var-declaration.js", "end": [ 1, 17 @@ -191,9 +182,9 @@ "filePaths": [ "var-declaration.js" ], - "sha1": "d58f0f3b2772c532d4abfb2617530a019c706fe1", + "sha1": "ed055ea2c0cdae06c2679c7febe33ea291ab50af", "gitDir": "test/corpus/repos/javascript", - "sha2": "e111e331012dbd7aeeaaf83940726e195ba543f8" + "sha2": "58c6d08bf25620f6b3be0ce0bde34968aa8731cb" } ,{ "testCaseDescription": "javascript-var-declaration-replacement-test", @@ -208,7 +199,6 @@ 1, 5 ], - "filepath": "var-declaration.js", "end": [ 1, 10 @@ -219,7 +209,6 @@ 1, 5 ], - "filepath": "var-declaration.js", "end": [ 1, 6 @@ -237,7 +226,6 @@ 1, 8 ], - "filepath": "var-declaration.js", "end": [ 1, 14 @@ -254,7 +242,6 @@ 1, 16 ], - "filepath": "var-declaration.js", "end": [ 1, 17 @@ -271,9 +258,9 @@ "filePaths": [ "var-declaration.js" ], - "sha1": "e111e331012dbd7aeeaaf83940726e195ba543f8", + "sha1": "58c6d08bf25620f6b3be0ce0bde34968aa8731cb", "gitDir": "test/corpus/repos/javascript", - "sha2": "0378ec81c520b2d1aab9e538654b953135c437cc" + "sha2": "b342a171c3b2487402c335c5073c5b3e9a6d9c28" } ,{ "testCaseDescription": "javascript-var-declaration-delete-replacement-test", @@ -287,7 +274,6 @@ 1, 5 ], - "filepath": "var-declaration.js", "end": [ 1, 6 @@ -304,7 +290,6 @@ 1, 8 ], - "filepath": "var-declaration.js", "end": [ 1, 14 @@ -321,7 +306,6 @@ 1, 16 ], - "filepath": "var-declaration.js", "end": [ 1, 17 @@ -338,7 +322,6 @@ 2, 5 ], - "filepath": "var-declaration.js", "end": [ 2, 10 @@ -355,7 +338,6 @@ 2, 5 ], - "filepath": "var-declaration.js", "end": [ 2, 6 @@ -372,7 +354,6 @@ 2, 8 ], - "filepath": "var-declaration.js", "end": [ 2, 14 @@ -389,7 +370,6 @@ 2, 16 ], - "filepath": "var-declaration.js", "end": [ 2, 17 @@ -406,9 +386,9 @@ "filePaths": [ "var-declaration.js" ], - "sha1": "0378ec81c520b2d1aab9e538654b953135c437cc", + "sha1": "b342a171c3b2487402c335c5073c5b3e9a6d9c28", "gitDir": "test/corpus/repos/javascript", - "sha2": "4115ce794c7d04607bd4b1664dd7fcef46aee907" + "sha2": "e7b32730438255bab8de8b0c76f204ef5d5517ec" } ,{ "testCaseDescription": "javascript-var-declaration-delete-test", @@ -422,7 +402,6 @@ 1, 5 ], - "filepath": "var-declaration.js", "end": [ 1, 10 @@ -439,9 +418,9 @@ "filePaths": [ "var-declaration.js" ], - "sha1": "4115ce794c7d04607bd4b1664dd7fcef46aee907", + "sha1": "e7b32730438255bab8de8b0c76f204ef5d5517ec", "gitDir": "test/corpus/repos/javascript", - "sha2": "8371b34923df7d07785117621099347de52fff5a" + "sha2": "9de9b7db92e589ace7505ab9b4db1c40ec631165" } ,{ "testCaseDescription": "javascript-var-declaration-delete-rest-test", @@ -455,7 +434,6 @@ 1, 5 ], - "filepath": "var-declaration.js", "end": [ 1, 6 @@ -472,7 +450,6 @@ 1, 8 ], - "filepath": "var-declaration.js", "end": [ 1, 14 @@ -489,7 +466,6 @@ 1, 16 ], - "filepath": "var-declaration.js", "end": [ 1, 17 @@ -506,7 +482,7 @@ "filePaths": [ "var-declaration.js" ], - "sha1": "8371b34923df7d07785117621099347de52fff5a", + "sha1": "9de9b7db92e589ace7505ab9b4db1c40ec631165", "gitDir": "test/corpus/repos/javascript", - "sha2": "d3f20de8481cbd432e9c90f5583e6e599473d75e" + "sha2": "f3566e32792c678aaed037ccd4998275a9c111f6" }] diff --git a/test/corpus/diff-summaries/javascript/variable.json b/test/corpus/diff-summaries/javascript/variable.json index 6b252e7c4..8f6371c24 100644 --- a/test/corpus/diff-summaries/javascript/variable.json +++ b/test/corpus/diff-summaries/javascript/variable.json @@ -10,7 +10,6 @@ 1, 1 ], - "filepath": "variable.js", "end": [ 1, 7 @@ -27,9 +26,9 @@ "filePaths": [ "variable.js" ], - "sha1": "c7aab3785be8b3fb5f2a62f600201f094b46e55b", + "sha1": "2074bb33669e57e62f87e701e4265cf784b19e58", "gitDir": "test/corpus/repos/javascript", - "sha2": "1aa695a28b82c1e2f6e45810958087df2a214382" + "sha2": "8b059350148dcffeee8ccd9366ad66c7d1cef915" } ,{ "testCaseDescription": "javascript-variable-replacement-insert-test", @@ -43,7 +42,6 @@ 1, 1 ], - "filepath": "variable.js", "end": [ 1, 8 @@ -60,7 +58,6 @@ 2, 1 ], - "filepath": "variable.js", "end": [ 2, 7 @@ -77,9 +74,9 @@ "filePaths": [ "variable.js" ], - "sha1": "1aa695a28b82c1e2f6e45810958087df2a214382", + "sha1": "8b059350148dcffeee8ccd9366ad66c7d1cef915", "gitDir": "test/corpus/repos/javascript", - "sha2": "80e312325ecad1c2f89d6ec9690f16acbb058e27" + "sha2": "90ab826472b30886ece143bfb81316b6a727943a" } ,{ "testCaseDescription": "javascript-variable-delete-insert-test", @@ -94,7 +91,6 @@ 1, 1 ], - "filepath": "variable.js", "end": [ 1, 8 @@ -105,7 +101,6 @@ 1, 1 ], - "filepath": "variable.js", "end": [ 1, 7 @@ -123,9 +118,9 @@ "filePaths": [ "variable.js" ], - "sha1": "80e312325ecad1c2f89d6ec9690f16acbb058e27", + "sha1": "90ab826472b30886ece143bfb81316b6a727943a", "gitDir": "test/corpus/repos/javascript", - "sha2": "0951a38d2aab78e7c9e08b0b45128afd29edbb54" + "sha2": "44ab672853770a8141287a7f6b99064f9138cb77" } ,{ "testCaseDescription": "javascript-variable-replacement-test", @@ -140,7 +135,6 @@ 1, 1 ], - "filepath": "variable.js", "end": [ 1, 7 @@ -151,7 +145,6 @@ 1, 1 ], - "filepath": "variable.js", "end": [ 1, 8 @@ -169,9 +162,9 @@ "filePaths": [ "variable.js" ], - "sha1": "0951a38d2aab78e7c9e08b0b45128afd29edbb54", + "sha1": "44ab672853770a8141287a7f6b99064f9138cb77", "gitDir": "test/corpus/repos/javascript", - "sha2": "6da8149bb0d7766abdc26bb7f9f73804f524e642" + "sha2": "5952e6fbb59faeda16dd0ce1ded38dcd90f1b587" } ,{ "testCaseDescription": "javascript-variable-delete-replacement-test", @@ -185,7 +178,6 @@ 1, 1 ], - "filepath": "variable.js", "end": [ 1, 8 @@ -202,7 +194,6 @@ 2, 1 ], - "filepath": "variable.js", "end": [ 2, 7 @@ -219,7 +210,6 @@ 2, 1 ], - "filepath": "variable.js", "end": [ 2, 8 @@ -236,9 +226,9 @@ "filePaths": [ "variable.js" ], - "sha1": "6da8149bb0d7766abdc26bb7f9f73804f524e642", + "sha1": "5952e6fbb59faeda16dd0ce1ded38dcd90f1b587", "gitDir": "test/corpus/repos/javascript", - "sha2": "2f6d1c166db7f528994372b9c607b7b3710c877e" + "sha2": "bf907d6d61c4fe246ce406e7fe04f0aafe39782c" } ,{ "testCaseDescription": "javascript-variable-delete-test", @@ -252,7 +242,6 @@ 1, 1 ], - "filepath": "variable.js", "end": [ 1, 7 @@ -269,9 +258,9 @@ "filePaths": [ "variable.js" ], - "sha1": "2f6d1c166db7f528994372b9c607b7b3710c877e", + "sha1": "bf907d6d61c4fe246ce406e7fe04f0aafe39782c", "gitDir": "test/corpus/repos/javascript", - "sha2": "5b6eb6f0a2f978d2f056987e03db2942c6fed3a0" + "sha2": "e044481441f48984c54cab43b37b7a07696be1c8" } ,{ "testCaseDescription": "javascript-variable-delete-rest-test", @@ -285,7 +274,6 @@ 1, 1 ], - "filepath": "variable.js", "end": [ 1, 8 @@ -302,7 +290,7 @@ "filePaths": [ "variable.js" ], - "sha1": "5b6eb6f0a2f978d2f056987e03db2942c6fed3a0", + "sha1": "e044481441f48984c54cab43b37b7a07696be1c8", "gitDir": "test/corpus/repos/javascript", - "sha2": "d284f40259b610bfb02c24b4693ef24e5f303e86" + "sha2": "1ecef9aa25c5f5b2d024632f76333266bbaa3b08" }] diff --git a/test/corpus/diff-summaries/javascript/void-operator.json b/test/corpus/diff-summaries/javascript/void-operator.json index 4dcdb4eb1..43f87d633 100644 --- a/test/corpus/diff-summaries/javascript/void-operator.json +++ b/test/corpus/diff-summaries/javascript/void-operator.json @@ -10,7 +10,6 @@ 1, 1 ], - "filepath": "void-operator.js", "end": [ 1, 9 @@ -27,9 +26,9 @@ "filePaths": [ "void-operator.js" ], - "sha1": "f6b6a39365ea495fba9ad72496f299b47250db15", + "sha1": "a34d26b577d45eb717e1fe5106677325581d96fb", "gitDir": "test/corpus/repos/javascript", - "sha2": "14275d131e692689d832b65982f8b52dd482477d" + "sha2": "509b527807b92bc977ea4d76352167537a31e59a" } ,{ "testCaseDescription": "javascript-void-operator-replacement-insert-test", @@ -43,7 +42,6 @@ 1, 1 ], - "filepath": "void-operator.js", "end": [ 1, 9 @@ -60,7 +58,6 @@ 2, 1 ], - "filepath": "void-operator.js", "end": [ 2, 9 @@ -77,9 +74,9 @@ "filePaths": [ "void-operator.js" ], - "sha1": "14275d131e692689d832b65982f8b52dd482477d", + "sha1": "509b527807b92bc977ea4d76352167537a31e59a", "gitDir": "test/corpus/repos/javascript", - "sha2": "9da3faf2138f4a5edb29d3da8d7714d018235814" + "sha2": "94643283de3ca9031814c2686d6981d061ea39e5" } ,{ "testCaseDescription": "javascript-void-operator-delete-insert-test", @@ -94,7 +91,6 @@ 1, 6 ], - "filepath": "void-operator.js", "end": [ 1, 7 @@ -105,7 +101,6 @@ 1, 6 ], - "filepath": "void-operator.js", "end": [ 1, 7 @@ -123,9 +118,9 @@ "filePaths": [ "void-operator.js" ], - "sha1": "9da3faf2138f4a5edb29d3da8d7714d018235814", + "sha1": "94643283de3ca9031814c2686d6981d061ea39e5", "gitDir": "test/corpus/repos/javascript", - "sha2": "6df23cc6c192c4276848ee9c2127891f7009de9f" + "sha2": "da299cf12b29b9a9e4c160c899a5a99f775db019" } ,{ "testCaseDescription": "javascript-void-operator-replacement-test", @@ -140,7 +135,6 @@ 1, 6 ], - "filepath": "void-operator.js", "end": [ 1, 7 @@ -151,7 +145,6 @@ 1, 6 ], - "filepath": "void-operator.js", "end": [ 1, 7 @@ -169,9 +162,9 @@ "filePaths": [ "void-operator.js" ], - "sha1": "6df23cc6c192c4276848ee9c2127891f7009de9f", + "sha1": "da299cf12b29b9a9e4c160c899a5a99f775db019", "gitDir": "test/corpus/repos/javascript", - "sha2": "6befaf0b0c702704c5f8ff3ad25219d48720668b" + "sha2": "f7257d8cc48c28fa362ac35b2ffe8a289ccda5b3" } ,{ "testCaseDescription": "javascript-void-operator-delete-replacement-test", @@ -185,7 +178,6 @@ 1, 1 ], - "filepath": "void-operator.js", "end": [ 1, 9 @@ -202,7 +194,6 @@ 2, 1 ], - "filepath": "void-operator.js", "end": [ 2, 9 @@ -219,7 +210,6 @@ 2, 1 ], - "filepath": "void-operator.js", "end": [ 2, 9 @@ -236,9 +226,9 @@ "filePaths": [ "void-operator.js" ], - "sha1": "6befaf0b0c702704c5f8ff3ad25219d48720668b", + "sha1": "f7257d8cc48c28fa362ac35b2ffe8a289ccda5b3", "gitDir": "test/corpus/repos/javascript", - "sha2": "e2adaa348d4cbaa1b6b45416d9dd70446d1c55e4" + "sha2": "eba77c9ca2f30769e008be446ac51602d8774949" } ,{ "testCaseDescription": "javascript-void-operator-delete-test", @@ -252,7 +242,6 @@ 1, 1 ], - "filepath": "void-operator.js", "end": [ 1, 9 @@ -269,9 +258,9 @@ "filePaths": [ "void-operator.js" ], - "sha1": "e2adaa348d4cbaa1b6b45416d9dd70446d1c55e4", + "sha1": "eba77c9ca2f30769e008be446ac51602d8774949", "gitDir": "test/corpus/repos/javascript", - "sha2": "c83da2b79a98b4da28801b470bc60d961784447b" + "sha2": "e2d838d6c0797077d1197573fcb31dab223f299b" } ,{ "testCaseDescription": "javascript-void-operator-delete-rest-test", @@ -285,7 +274,6 @@ 1, 1 ], - "filepath": "void-operator.js", "end": [ 1, 9 @@ -302,7 +290,7 @@ "filePaths": [ "void-operator.js" ], - "sha1": "c83da2b79a98b4da28801b470bc60d961784447b", + "sha1": "e2d838d6c0797077d1197573fcb31dab223f299b", "gitDir": "test/corpus/repos/javascript", - "sha2": "f0aa5967e70024ba3cff3ab45027fc5cc4ee095e" + "sha2": "f79e1375ce21269c7d54de075cbed5f40ea1b501" }] diff --git a/test/corpus/diff-summaries/javascript/while-statement.json b/test/corpus/diff-summaries/javascript/while-statement.json index 48a9686f8..a81fc6bd3 100644 --- a/test/corpus/diff-summaries/javascript/while-statement.json +++ b/test/corpus/diff-summaries/javascript/while-statement.json @@ -10,7 +10,6 @@ 1, 1 ], - "filepath": "while-statement.js", "end": [ 1, 19 @@ -27,9 +26,9 @@ "filePaths": [ "while-statement.js" ], - "sha1": "9f4f05255cc1f41d2c7dcbe4a450082306db1db1", + "sha1": "126641b1c820ff0a55da55b367554ff1698a4fc3", "gitDir": "test/corpus/repos/javascript", - "sha2": "01e25ad7f0556ec7b0f06ef99919a864786e93ba" + "sha2": "9c434e0c6b44a4e60ca5b0bed09dbaef6224bc86" } ,{ "testCaseDescription": "javascript-while-statement-replacement-insert-test", @@ -43,7 +42,6 @@ 1, 1 ], - "filepath": "while-statement.js", "end": [ 1, 19 @@ -60,7 +58,6 @@ 2, 1 ], - "filepath": "while-statement.js", "end": [ 2, 19 @@ -77,9 +74,9 @@ "filePaths": [ "while-statement.js" ], - "sha1": "01e25ad7f0556ec7b0f06ef99919a864786e93ba", + "sha1": "9c434e0c6b44a4e60ca5b0bed09dbaef6224bc86", "gitDir": "test/corpus/repos/javascript", - "sha2": "982eff438a463f6903946a091a08dfcaaa80ecd8" + "sha2": "0c64c82fc19f9a9f7598962e6a629eda732414c4" } ,{ "testCaseDescription": "javascript-while-statement-delete-insert-test", @@ -94,7 +91,6 @@ 1, 8 ], - "filepath": "while-statement.js", "end": [ 1, 9 @@ -105,7 +101,6 @@ 1, 8 ], - "filepath": "while-statement.js", "end": [ 1, 9 @@ -124,7 +119,6 @@ 1, 13 ], - "filepath": "while-statement.js", "end": [ 1, 14 @@ -135,7 +129,6 @@ 1, 13 ], - "filepath": "while-statement.js", "end": [ 1, 14 @@ -153,9 +146,9 @@ "filePaths": [ "while-statement.js" ], - "sha1": "982eff438a463f6903946a091a08dfcaaa80ecd8", + "sha1": "0c64c82fc19f9a9f7598962e6a629eda732414c4", "gitDir": "test/corpus/repos/javascript", - "sha2": "19ec60f47bbb298370319dcab87351c3cc1d8724" + "sha2": "ebc38db083a37927879c8a7896d84c6ad670bd41" } ,{ "testCaseDescription": "javascript-while-statement-replacement-test", @@ -170,7 +163,6 @@ 1, 8 ], - "filepath": "while-statement.js", "end": [ 1, 9 @@ -181,7 +173,6 @@ 1, 8 ], - "filepath": "while-statement.js", "end": [ 1, 9 @@ -200,7 +191,6 @@ 1, 13 ], - "filepath": "while-statement.js", "end": [ 1, 14 @@ -211,7 +201,6 @@ 1, 13 ], - "filepath": "while-statement.js", "end": [ 1, 14 @@ -229,9 +218,9 @@ "filePaths": [ "while-statement.js" ], - "sha1": "19ec60f47bbb298370319dcab87351c3cc1d8724", + "sha1": "ebc38db083a37927879c8a7896d84c6ad670bd41", "gitDir": "test/corpus/repos/javascript", - "sha2": "483304d2361d6a96a00e8e9fc17ff6c934d44129" + "sha2": "a2a000e2b77ba785dc25df73cc387a4fff5fd6ce" } ,{ "testCaseDescription": "javascript-while-statement-delete-replacement-test", @@ -245,7 +234,6 @@ 1, 1 ], - "filepath": "while-statement.js", "end": [ 1, 19 @@ -262,7 +250,6 @@ 2, 1 ], - "filepath": "while-statement.js", "end": [ 2, 19 @@ -279,7 +266,6 @@ 2, 1 ], - "filepath": "while-statement.js", "end": [ 2, 19 @@ -296,9 +282,9 @@ "filePaths": [ "while-statement.js" ], - "sha1": "483304d2361d6a96a00e8e9fc17ff6c934d44129", + "sha1": "a2a000e2b77ba785dc25df73cc387a4fff5fd6ce", "gitDir": "test/corpus/repos/javascript", - "sha2": "5b474876098ede922a392c2de9177a419ca30113" + "sha2": "1766bc7de3028114c029d58d8dad57d1b224b56f" } ,{ "testCaseDescription": "javascript-while-statement-delete-test", @@ -312,7 +298,6 @@ 1, 1 ], - "filepath": "while-statement.js", "end": [ 1, 19 @@ -329,9 +314,9 @@ "filePaths": [ "while-statement.js" ], - "sha1": "5b474876098ede922a392c2de9177a419ca30113", + "sha1": "1766bc7de3028114c029d58d8dad57d1b224b56f", "gitDir": "test/corpus/repos/javascript", - "sha2": "ee2a8c56d95104cb85caedc24c2bc70ae85dc0a7" + "sha2": "7acae0fbb45845daa0c4054e20d30aff3f37b872" } ,{ "testCaseDescription": "javascript-while-statement-delete-rest-test", @@ -345,7 +330,6 @@ 1, 1 ], - "filepath": "while-statement.js", "end": [ 1, 19 @@ -362,7 +346,7 @@ "filePaths": [ "while-statement.js" ], - "sha1": "ee2a8c56d95104cb85caedc24c2bc70ae85dc0a7", + "sha1": "7acae0fbb45845daa0c4054e20d30aff3f37b872", "gitDir": "test/corpus/repos/javascript", - "sha2": "1dfeac8c9e51379d4ffcbc1b381c7a6b88ce13bf" + "sha2": "ae76dbf085fd365417c914186052f77fec683519" }] diff --git a/test/corpus/repos/javascript b/test/corpus/repos/javascript index 725a0ee6c..a1ec5326a 160000 --- a/test/corpus/repos/javascript +++ b/test/corpus/repos/javascript @@ -1 +1 @@ -Subproject commit 725a0ee6c4535512f82e53d65edf151cc8f724eb +Subproject commit a1ec5326a248592c7deb7a7e3b3ece00b97506bb From 6ba48666ede17159d53524264dd20af2532f2716 Mon Sep 17 00:00:00 2001 From: joshvera Date: Tue, 11 Oct 2016 16:17:34 -0400 Subject: [PATCH 27/27] bump files --- src/DiffSummary.hs | 6 +- .../javascript/anonymous-function.json | 76 ++- .../anonymous-parameterless-function.json | 58 +-- .../diff-summaries/javascript/array.json | 58 +-- .../javascript/arrow-function.json | 58 +-- .../diff-summaries/javascript/assignment.json | 58 +-- .../javascript/bitwise-operator.json | 58 +-- .../javascript/boolean-operator.json | 46 +- .../javascript/chained-callbacks.json | 70 ++- .../javascript/chained-property-access.json | 64 +-- .../diff-summaries/javascript/class.json | 70 ++- .../javascript/comma-operator.json | 82 ++-- .../diff-summaries/javascript/comment.json | 58 +-- .../javascript/constructor-call.json | 58 +-- .../javascript/delete-operator.json | 58 +-- .../javascript/do-while-statement.json | 64 +-- .../diff-summaries/javascript/false.json | 64 +-- .../javascript/for-in-statement.json | 70 ++- .../for-loop-with-in-statement.json | 64 +-- .../javascript/for-of-statement.json | 70 ++- .../javascript/for-statement.json | 58 +-- .../javascript/function-call-args.json | 88 ++-- .../javascript/function-call.json | 58 +-- .../diff-summaries/javascript/function.json | 58 +-- .../javascript/generator-function.json | 58 +-- .../diff-summaries/javascript/identifier.json | 58 +-- .../diff-summaries/javascript/if-else.json | 58 +-- test/corpus/diff-summaries/javascript/if.json | 58 +-- .../diff-summaries/javascript/import.json | 334 +++++-------- .../javascript/math-assignment-operator.json | 58 +-- .../javascript/math-operator.json | 64 +-- .../javascript/member-access-assignment.json | 58 +-- .../javascript/member-access.json | 58 +-- .../javascript/method-call.json | 58 +-- .../javascript/named-function.json | 82 ++-- .../nested-do-while-in-function.json | 457 ++++++------------ .../javascript/nested-functions.json | 64 +-- .../diff-summaries/javascript/null.json | 64 +-- .../diff-summaries/javascript/number.json | 58 +-- .../javascript/object-with-methods.json | 58 +-- .../diff-summaries/javascript/object.json | 64 +-- .../diff-summaries/javascript/regex.json | 58 +-- .../javascript/relational-operator.json | 46 +- .../javascript/return-statement.json | 58 +-- .../diff-summaries/javascript/string.json | 58 +-- .../subscript-access-assignment.json | 58 +-- .../javascript/subscript-access-string.json | 58 +-- .../javascript/subscript-access-variable.json | 58 +-- .../javascript/switch-statement.json | 64 +-- .../javascript/template-string.json | 58 +-- .../diff-summaries/javascript/ternary.json | 64 +-- .../javascript/this-expression.json | 64 +-- .../javascript/throw-statement.json | 58 +-- .../diff-summaries/javascript/true.json | 64 +-- .../javascript/try-statement.json | 64 +-- .../javascript/type-operator.json | 58 +-- .../diff-summaries/javascript/undefined.json | 64 +-- .../javascript/var-declaration.json | 94 ++-- .../diff-summaries/javascript/variable.json | 58 +-- .../javascript/void-operator.json | 58 +-- .../javascript/while-statement.json | 64 +-- test/corpus/repos/javascript | 2 +- 62 files changed, 1753 insertions(+), 2656 deletions(-) diff --git a/src/DiffSummary.hs b/src/DiffSummary.hs index dc120d1ef..9d76c0e89 100644 --- a/src/DiffSummary.hs +++ b/src/DiffSummary.hs @@ -56,7 +56,11 @@ identifiable term = isIdentifiable (unwrap term) term data JSONSummary summary span = JSONSummary { summary :: summary, span :: span } | ErrorSummary { summary :: summary, span :: span } - deriving (ToJSON, Generic, Eq, Show) + deriving (Generic, Eq, Show) + +instance (ToJSON summary, ToJSON span) => ToJSON (JSONSummary summary span) where + toJSON JSONSummary{..} = object [ "summary" .= summary, "span" .= span ] + toJSON ErrorSummary{..} = object [ "summary" .= summary, "span" .= span ] isErrorSummary :: JSONSummary summary span -> Bool isErrorSummary ErrorSummary{} = True diff --git a/test/corpus/diff-summaries/javascript/anonymous-function.json b/test/corpus/diff-summaries/javascript/anonymous-function.json index ad31e86fb..5f9b3c064 100644 --- a/test/corpus/diff-summaries/javascript/anonymous-function.json +++ b/test/corpus/diff-summaries/javascript/anonymous-function.json @@ -16,8 +16,7 @@ ] } }, - "summary": "Added an anonymous(a, b) function", - "tag": "JSONSummary" + "summary": "Added an anonymous(a, b) function" } ] }, @@ -26,9 +25,9 @@ "filePaths": [ "anonymous-function.js" ], - "sha1": "9a3c8e5bfb1ca123cfbbeefbe9069ecc0bb85fa4", + "sha1": "4eda6b0a46046cb99a4544fe3a4a9c23e702eeac", "gitDir": "test/corpus/repos/javascript", - "sha2": "499d32d46d3eb5785dbb27e3b56a0894823ee9dd" + "sha2": "0ae1cc9281ef60c31e19985b68713eb40fc2ad2c" } ,{ "testCaseDescription": "javascript-anonymous-function-replacement-insert-test", @@ -48,8 +47,7 @@ ] } }, - "summary": "Added an anonymous(b, c) function", - "tag": "JSONSummary" + "summary": "Added an anonymous(b, c) function" }, { "span": { @@ -64,8 +62,7 @@ ] } }, - "summary": "Added an anonymous(a, b) function", - "tag": "JSONSummary" + "summary": "Added an anonymous(a, b) function" } ] }, @@ -74,9 +71,9 @@ "filePaths": [ "anonymous-function.js" ], - "sha1": "499d32d46d3eb5785dbb27e3b56a0894823ee9dd", + "sha1": "0ae1cc9281ef60c31e19985b68713eb40fc2ad2c", "gitDir": "test/corpus/repos/javascript", - "sha2": "20922f45f08fe649a067e60016ed60a67c2c1c7e" + "sha2": "e13ea092e21306d5e46e6bf1a2a18566873475d2" } ,{ "testCaseDescription": "javascript-anonymous-function-delete-insert-test", @@ -108,8 +105,7 @@ } ] }, - "summary": "Replaced the 'b' identifier with the 'a' identifier", - "tag": "JSONSummary" + "summary": "Replaced the 'b' identifier with the 'a' identifier" }, { "span": { @@ -136,8 +132,7 @@ } ] }, - "summary": "Replaced the 'c' identifier with the 'b' identifier", - "tag": "JSONSummary" + "summary": "Replaced the 'c' identifier with the 'b' identifier" }, { "span": { @@ -164,8 +159,7 @@ } ] }, - "summary": "Replaced the 'b' identifier with the 'a' identifier", - "tag": "JSONSummary" + "summary": "Replaced the 'b' identifier with the 'a' identifier" }, { "span": { @@ -192,8 +186,7 @@ } ] }, - "summary": "Replaced the 'c' identifier with the 'b' identifier", - "tag": "JSONSummary" + "summary": "Replaced the 'c' identifier with the 'b' identifier" } ] }, @@ -202,9 +195,9 @@ "filePaths": [ "anonymous-function.js" ], - "sha1": "20922f45f08fe649a067e60016ed60a67c2c1c7e", + "sha1": "e13ea092e21306d5e46e6bf1a2a18566873475d2", "gitDir": "test/corpus/repos/javascript", - "sha2": "6fc93b6614e4cfff72463ca12e9987c14fb24c6f" + "sha2": "664b50f840363802e3fc974ae60831dc4e13d5c2" } ,{ "testCaseDescription": "javascript-anonymous-function-replacement-test", @@ -236,8 +229,7 @@ } ] }, - "summary": "Replaced the 'a' identifier with the 'b' identifier", - "tag": "JSONSummary" + "summary": "Replaced the 'a' identifier with the 'b' identifier" }, { "span": { @@ -264,8 +256,7 @@ } ] }, - "summary": "Replaced the 'b' identifier with the 'c' identifier", - "tag": "JSONSummary" + "summary": "Replaced the 'b' identifier with the 'c' identifier" }, { "span": { @@ -292,8 +283,7 @@ } ] }, - "summary": "Replaced the 'a' identifier with the 'b' identifier", - "tag": "JSONSummary" + "summary": "Replaced the 'a' identifier with the 'b' identifier" }, { "span": { @@ -320,8 +310,7 @@ } ] }, - "summary": "Replaced the 'b' identifier with the 'c' identifier", - "tag": "JSONSummary" + "summary": "Replaced the 'b' identifier with the 'c' identifier" } ] }, @@ -330,9 +319,9 @@ "filePaths": [ "anonymous-function.js" ], - "sha1": "6fc93b6614e4cfff72463ca12e9987c14fb24c6f", + "sha1": "664b50f840363802e3fc974ae60831dc4e13d5c2", "gitDir": "test/corpus/repos/javascript", - "sha2": "c6ba2db9ae426f80263c615cc53d465d3e20417b" + "sha2": "f0b28a88b5b36ac5eb6770e80f5455c5c2ae3396" } ,{ "testCaseDescription": "javascript-anonymous-function-delete-replacement-test", @@ -352,8 +341,7 @@ ] } }, - "summary": "Deleted an anonymous(b, c) function", - "tag": "JSONSummary" + "summary": "Deleted an anonymous(b, c) function" }, { "span": { @@ -368,8 +356,7 @@ ] } }, - "summary": "Deleted an anonymous(a, b) function", - "tag": "JSONSummary" + "summary": "Deleted an anonymous(a, b) function" }, { "span": { @@ -384,8 +371,7 @@ ] } }, - "summary": "Added an anonymous(b, c) function", - "tag": "JSONSummary" + "summary": "Added an anonymous(b, c) function" } ] }, @@ -394,9 +380,9 @@ "filePaths": [ "anonymous-function.js" ], - "sha1": "c6ba2db9ae426f80263c615cc53d465d3e20417b", + "sha1": "f0b28a88b5b36ac5eb6770e80f5455c5c2ae3396", "gitDir": "test/corpus/repos/javascript", - "sha2": "95ca98c8ae2cc3b0eac592b39529678fbc60cb5e" + "sha2": "2e8bd85c462e82c1de6ad1d016dec89b8f6c7a94" } ,{ "testCaseDescription": "javascript-anonymous-function-delete-test", @@ -416,8 +402,7 @@ ] } }, - "summary": "Deleted an anonymous(a, b) function", - "tag": "JSONSummary" + "summary": "Deleted an anonymous(a, b) function" } ] }, @@ -426,9 +411,9 @@ "filePaths": [ "anonymous-function.js" ], - "sha1": "95ca98c8ae2cc3b0eac592b39529678fbc60cb5e", + "sha1": "2e8bd85c462e82c1de6ad1d016dec89b8f6c7a94", "gitDir": "test/corpus/repos/javascript", - "sha2": "fdc9c77b584391d5efc4ee112d766985422eccc3" + "sha2": "8730cf111655ff909dd1b3a43b8afb78bc05f7b5" } ,{ "testCaseDescription": "javascript-anonymous-function-delete-rest-test", @@ -448,8 +433,7 @@ ] } }, - "summary": "Deleted an anonymous(b, c) function", - "tag": "JSONSummary" + "summary": "Deleted an anonymous(b, c) function" } ] }, @@ -458,7 +442,7 @@ "filePaths": [ "anonymous-function.js" ], - "sha1": "fdc9c77b584391d5efc4ee112d766985422eccc3", + "sha1": "8730cf111655ff909dd1b3a43b8afb78bc05f7b5", "gitDir": "test/corpus/repos/javascript", - "sha2": "d4b2414c028e39dae3876a16e6b0b213320be351" + "sha2": "0a29e7e55f31e31e4f830f33dd8b1a6231165888" }] diff --git a/test/corpus/diff-summaries/javascript/anonymous-parameterless-function.json b/test/corpus/diff-summaries/javascript/anonymous-parameterless-function.json index 3a11da3ee..3ee3eb6d9 100644 --- a/test/corpus/diff-summaries/javascript/anonymous-parameterless-function.json +++ b/test/corpus/diff-summaries/javascript/anonymous-parameterless-function.json @@ -16,8 +16,7 @@ ] } }, - "summary": "Added an anonymous() function", - "tag": "JSONSummary" + "summary": "Added an anonymous() function" } ] }, @@ -26,9 +25,9 @@ "filePaths": [ "anonymous-parameterless-function.js" ], - "sha1": "22b6b91906964ec80192f4d30f12125b99e1cad4", + "sha1": "972c476a86993546e4da7dd3f2c488b455ff24db", "gitDir": "test/corpus/repos/javascript", - "sha2": "e41f44ca896e7de4bffa968df9bbf1b1caea1e04" + "sha2": "3e2289ebea24250dc463db0603223b2ad7233e39" } ,{ "testCaseDescription": "javascript-anonymous-parameterless-function-replacement-insert-test", @@ -48,8 +47,7 @@ ] } }, - "summary": "Added an anonymous() function", - "tag": "JSONSummary" + "summary": "Added an anonymous() function" }, { "span": { @@ -64,8 +62,7 @@ ] } }, - "summary": "Added an anonymous() function", - "tag": "JSONSummary" + "summary": "Added an anonymous() function" } ] }, @@ -74,9 +71,9 @@ "filePaths": [ "anonymous-parameterless-function.js" ], - "sha1": "e41f44ca896e7de4bffa968df9bbf1b1caea1e04", + "sha1": "3e2289ebea24250dc463db0603223b2ad7233e39", "gitDir": "test/corpus/repos/javascript", - "sha2": "213068fb89e1381ab15b652ee2f6e16994a6ac16" + "sha2": "281d67dce183a41f664372f47fce3f51b32cdb3a" } ,{ "testCaseDescription": "javascript-anonymous-parameterless-function-delete-insert-test", @@ -108,8 +105,7 @@ } ] }, - "summary": "Replaced the 'hello' string with the 'hi' string", - "tag": "JSONSummary" + "summary": "Replaced the 'hello' string with the 'hi' string" } ] }, @@ -118,9 +114,9 @@ "filePaths": [ "anonymous-parameterless-function.js" ], - "sha1": "213068fb89e1381ab15b652ee2f6e16994a6ac16", + "sha1": "281d67dce183a41f664372f47fce3f51b32cdb3a", "gitDir": "test/corpus/repos/javascript", - "sha2": "e32940ed8b6044088622ac48c96708bac78d9fe2" + "sha2": "7c730f2014c719d3a12b578babf30f6c2c56c966" } ,{ "testCaseDescription": "javascript-anonymous-parameterless-function-replacement-test", @@ -152,8 +148,7 @@ } ] }, - "summary": "Replaced the 'hi' string with the 'hello' string", - "tag": "JSONSummary" + "summary": "Replaced the 'hi' string with the 'hello' string" } ] }, @@ -162,9 +157,9 @@ "filePaths": [ "anonymous-parameterless-function.js" ], - "sha1": "e32940ed8b6044088622ac48c96708bac78d9fe2", + "sha1": "7c730f2014c719d3a12b578babf30f6c2c56c966", "gitDir": "test/corpus/repos/javascript", - "sha2": "7ff2f9753b8b8a5c06187ba407bddb72742d4d2b" + "sha2": "2917edeb872ab9a847651f3df4d3fe0707f410a8" } ,{ "testCaseDescription": "javascript-anonymous-parameterless-function-delete-replacement-test", @@ -184,8 +179,7 @@ ] } }, - "summary": "Deleted an anonymous() function", - "tag": "JSONSummary" + "summary": "Deleted an anonymous() function" }, { "span": { @@ -200,8 +194,7 @@ ] } }, - "summary": "Deleted an anonymous() function", - "tag": "JSONSummary" + "summary": "Deleted an anonymous() function" }, { "span": { @@ -216,8 +209,7 @@ ] } }, - "summary": "Added an anonymous() function", - "tag": "JSONSummary" + "summary": "Added an anonymous() function" } ] }, @@ -226,9 +218,9 @@ "filePaths": [ "anonymous-parameterless-function.js" ], - "sha1": "7ff2f9753b8b8a5c06187ba407bddb72742d4d2b", + "sha1": "2917edeb872ab9a847651f3df4d3fe0707f410a8", "gitDir": "test/corpus/repos/javascript", - "sha2": "7aff9964814159468da7f26875cf415b3558eee4" + "sha2": "1cc8d6469e2bb265ac93a2c5e75c5a692cf37610" } ,{ "testCaseDescription": "javascript-anonymous-parameterless-function-delete-test", @@ -248,8 +240,7 @@ ] } }, - "summary": "Deleted an anonymous() function", - "tag": "JSONSummary" + "summary": "Deleted an anonymous() function" } ] }, @@ -258,9 +249,9 @@ "filePaths": [ "anonymous-parameterless-function.js" ], - "sha1": "7aff9964814159468da7f26875cf415b3558eee4", + "sha1": "1cc8d6469e2bb265ac93a2c5e75c5a692cf37610", "gitDir": "test/corpus/repos/javascript", - "sha2": "68beb683ce57c3149995ad763f201f4a6836ce2b" + "sha2": "844cb44d31f4dfae4a7f6d71c968c1f7ed98a728" } ,{ "testCaseDescription": "javascript-anonymous-parameterless-function-delete-rest-test", @@ -280,8 +271,7 @@ ] } }, - "summary": "Deleted an anonymous() function", - "tag": "JSONSummary" + "summary": "Deleted an anonymous() function" } ] }, @@ -290,7 +280,7 @@ "filePaths": [ "anonymous-parameterless-function.js" ], - "sha1": "68beb683ce57c3149995ad763f201f4a6836ce2b", + "sha1": "844cb44d31f4dfae4a7f6d71c968c1f7ed98a728", "gitDir": "test/corpus/repos/javascript", - "sha2": "b0658b075e567097a50079f320b747eb442b7fe6" + "sha2": "99592bbf904b69053a764508c8b7e2113f456e77" }] diff --git a/test/corpus/diff-summaries/javascript/array.json b/test/corpus/diff-summaries/javascript/array.json index b19918c46..6032f88c4 100644 --- a/test/corpus/diff-summaries/javascript/array.json +++ b/test/corpus/diff-summaries/javascript/array.json @@ -16,8 +16,7 @@ ] } }, - "summary": "Added the '[ \"item1\" ]' array", - "tag": "JSONSummary" + "summary": "Added the '[ \"item1\" ]' array" } ] }, @@ -26,9 +25,9 @@ "filePaths": [ "array.js" ], - "sha1": "2eae8fefa77d6a4d6f762811f764fb0194e0c694", + "sha1": "bc7b1f8621267ae931d598deec486fc92bccc736", "gitDir": "test/corpus/repos/javascript", - "sha2": "a0220a9f702e60c8fc2a51af41d6c44fb0caef87" + "sha2": "1f5c0ab465c11956cade7def7f18df96c823d8d4" } ,{ "testCaseDescription": "javascript-array-replacement-insert-test", @@ -48,8 +47,7 @@ ] } }, - "summary": "Added the '[ \"item1\", \"item2\" ]' array", - "tag": "JSONSummary" + "summary": "Added the '[ \"item1\", \"item2\" ]' array" }, { "span": { @@ -64,8 +62,7 @@ ] } }, - "summary": "Added the '[ \"item1\" ]' array", - "tag": "JSONSummary" + "summary": "Added the '[ \"item1\" ]' array" } ] }, @@ -74,9 +71,9 @@ "filePaths": [ "array.js" ], - "sha1": "a0220a9f702e60c8fc2a51af41d6c44fb0caef87", + "sha1": "1f5c0ab465c11956cade7def7f18df96c823d8d4", "gitDir": "test/corpus/repos/javascript", - "sha2": "4a15d2534dd78648fdb6d009ac7d300366a3fcd1" + "sha2": "9eddf6e3cb0a349128bd8900cdf17e43492227da" } ,{ "testCaseDescription": "javascript-array-delete-insert-test", @@ -96,8 +93,7 @@ ] } }, - "summary": "Deleted the \"item2\" string", - "tag": "JSONSummary" + "summary": "Deleted the \"item2\" string" } ] }, @@ -106,9 +102,9 @@ "filePaths": [ "array.js" ], - "sha1": "4a15d2534dd78648fdb6d009ac7d300366a3fcd1", + "sha1": "9eddf6e3cb0a349128bd8900cdf17e43492227da", "gitDir": "test/corpus/repos/javascript", - "sha2": "d88be4ec5b1f423eb9e9f43d8bc330029c45d46e" + "sha2": "b13b543138e791710292fdf81def6f8d528e8643" } ,{ "testCaseDescription": "javascript-array-replacement-test", @@ -128,8 +124,7 @@ ] } }, - "summary": "Added the \"item2\" string", - "tag": "JSONSummary" + "summary": "Added the \"item2\" string" } ] }, @@ -138,9 +133,9 @@ "filePaths": [ "array.js" ], - "sha1": "d88be4ec5b1f423eb9e9f43d8bc330029c45d46e", + "sha1": "b13b543138e791710292fdf81def6f8d528e8643", "gitDir": "test/corpus/repos/javascript", - "sha2": "b59e1420e44e05650233fd4d4d8de7d800209108" + "sha2": "4dd191872b1355fdd5afeb5bc36f086b7a7cbd73" } ,{ "testCaseDescription": "javascript-array-delete-replacement-test", @@ -160,8 +155,7 @@ ] } }, - "summary": "Deleted the '[ \"item1\", \"item2\" ]' array", - "tag": "JSONSummary" + "summary": "Deleted the '[ \"item1\", \"item2\" ]' array" }, { "span": { @@ -176,8 +170,7 @@ ] } }, - "summary": "Deleted the '[ \"item1\" ]' array", - "tag": "JSONSummary" + "summary": "Deleted the '[ \"item1\" ]' array" }, { "span": { @@ -192,8 +185,7 @@ ] } }, - "summary": "Added the '[ \"item1\", \"item2\" ]' array", - "tag": "JSONSummary" + "summary": "Added the '[ \"item1\", \"item2\" ]' array" } ] }, @@ -202,9 +194,9 @@ "filePaths": [ "array.js" ], - "sha1": "b59e1420e44e05650233fd4d4d8de7d800209108", + "sha1": "4dd191872b1355fdd5afeb5bc36f086b7a7cbd73", "gitDir": "test/corpus/repos/javascript", - "sha2": "793c9c44d26a5d2cf79c81a10ac7efdba52feb3a" + "sha2": "5434cf6d92267f23a08cf961d1f715d9d67d7611" } ,{ "testCaseDescription": "javascript-array-delete-test", @@ -224,8 +216,7 @@ ] } }, - "summary": "Deleted the '[ \"item1\" ]' array", - "tag": "JSONSummary" + "summary": "Deleted the '[ \"item1\" ]' array" } ] }, @@ -234,9 +225,9 @@ "filePaths": [ "array.js" ], - "sha1": "793c9c44d26a5d2cf79c81a10ac7efdba52feb3a", + "sha1": "5434cf6d92267f23a08cf961d1f715d9d67d7611", "gitDir": "test/corpus/repos/javascript", - "sha2": "c618daa36f536027c9d7f6e46a90ec22076fdcbf" + "sha2": "d58141388b2aa0186ceb0db2deeeb7524540486a" } ,{ "testCaseDescription": "javascript-array-delete-rest-test", @@ -256,8 +247,7 @@ ] } }, - "summary": "Deleted the '[ \"item1\", \"item2\" ]' array", - "tag": "JSONSummary" + "summary": "Deleted the '[ \"item1\", \"item2\" ]' array" } ] }, @@ -266,7 +256,7 @@ "filePaths": [ "array.js" ], - "sha1": "c618daa36f536027c9d7f6e46a90ec22076fdcbf", + "sha1": "d58141388b2aa0186ceb0db2deeeb7524540486a", "gitDir": "test/corpus/repos/javascript", - "sha2": "1a2d64688174370f61c0962a2cd96be5f1758ccc" + "sha2": "33c7a858a16464d6fe8e27c69fc09f986fb56dae" }] diff --git a/test/corpus/diff-summaries/javascript/arrow-function.json b/test/corpus/diff-summaries/javascript/arrow-function.json index 2b6fdaf91..e0b71957a 100644 --- a/test/corpus/diff-summaries/javascript/arrow-function.json +++ b/test/corpus/diff-summaries/javascript/arrow-function.json @@ -16,8 +16,7 @@ ] } }, - "summary": "Added an anonymous(f, g) function", - "tag": "JSONSummary" + "summary": "Added an anonymous(f, g) function" } ] }, @@ -26,9 +25,9 @@ "filePaths": [ "arrow-function.js" ], - "sha1": "1cb91e98d1764fe8fb5c2a7798c9173523abdb1b", + "sha1": "b784ecef530da4646deff5aaff5d1263aa216ef3", "gitDir": "test/corpus/repos/javascript", - "sha2": "cabe717d9de437bbcf599b358c40bd1a9f7497c5" + "sha2": "b981ec4fb5850f454c25389b3cccdb678e94f626" } ,{ "testCaseDescription": "javascript-arrow-function-replacement-insert-test", @@ -48,8 +47,7 @@ ] } }, - "summary": "Added an anonymous(f, g) function", - "tag": "JSONSummary" + "summary": "Added an anonymous(f, g) function" }, { "span": { @@ -64,8 +62,7 @@ ] } }, - "summary": "Added an anonymous(f, g) function", - "tag": "JSONSummary" + "summary": "Added an anonymous(f, g) function" } ] }, @@ -74,9 +71,9 @@ "filePaths": [ "arrow-function.js" ], - "sha1": "cabe717d9de437bbcf599b358c40bd1a9f7497c5", + "sha1": "b981ec4fb5850f454c25389b3cccdb678e94f626", "gitDir": "test/corpus/repos/javascript", - "sha2": "81833f1dfc5306bdf83101de4a514162c004f133" + "sha2": "419347ea5418439d6c4a0400799eef9ffe6ef5d2" } ,{ "testCaseDescription": "javascript-arrow-function-delete-insert-test", @@ -108,8 +105,7 @@ } ] }, - "summary": "Replaced the 'g' identifier with the 'h' identifier", - "tag": "JSONSummary" + "summary": "Replaced the 'g' identifier with the 'h' identifier" } ] }, @@ -118,9 +114,9 @@ "filePaths": [ "arrow-function.js" ], - "sha1": "81833f1dfc5306bdf83101de4a514162c004f133", + "sha1": "419347ea5418439d6c4a0400799eef9ffe6ef5d2", "gitDir": "test/corpus/repos/javascript", - "sha2": "1477c3eb5d6b3fb17e658851e597548a27e9aee5" + "sha2": "c427f86b3d74e6605ac82591f26649df704049ce" } ,{ "testCaseDescription": "javascript-arrow-function-replacement-test", @@ -152,8 +148,7 @@ } ] }, - "summary": "Replaced the 'h' identifier with the 'g' identifier", - "tag": "JSONSummary" + "summary": "Replaced the 'h' identifier with the 'g' identifier" } ] }, @@ -162,9 +157,9 @@ "filePaths": [ "arrow-function.js" ], - "sha1": "1477c3eb5d6b3fb17e658851e597548a27e9aee5", + "sha1": "c427f86b3d74e6605ac82591f26649df704049ce", "gitDir": "test/corpus/repos/javascript", - "sha2": "792510a28547ef00fb3f427f0588a350070b78c8" + "sha2": "89d1b4d2d18912e6cd8a0add7948ee3c8163a399" } ,{ "testCaseDescription": "javascript-arrow-function-delete-replacement-test", @@ -184,8 +179,7 @@ ] } }, - "summary": "Deleted an anonymous(f, g) function", - "tag": "JSONSummary" + "summary": "Deleted an anonymous(f, g) function" }, { "span": { @@ -200,8 +194,7 @@ ] } }, - "summary": "Deleted an anonymous(f, g) function", - "tag": "JSONSummary" + "summary": "Deleted an anonymous(f, g) function" }, { "span": { @@ -216,8 +209,7 @@ ] } }, - "summary": "Added an anonymous(f, g) function", - "tag": "JSONSummary" + "summary": "Added an anonymous(f, g) function" } ] }, @@ -226,9 +218,9 @@ "filePaths": [ "arrow-function.js" ], - "sha1": "792510a28547ef00fb3f427f0588a350070b78c8", + "sha1": "89d1b4d2d18912e6cd8a0add7948ee3c8163a399", "gitDir": "test/corpus/repos/javascript", - "sha2": "43d4dec7b3f7190611127a9184ba1b8c7ef95581" + "sha2": "a77f256f44bf9d478cea9072b568053dfdfd7ff6" } ,{ "testCaseDescription": "javascript-arrow-function-delete-test", @@ -248,8 +240,7 @@ ] } }, - "summary": "Deleted an anonymous(f, g) function", - "tag": "JSONSummary" + "summary": "Deleted an anonymous(f, g) function" } ] }, @@ -258,9 +249,9 @@ "filePaths": [ "arrow-function.js" ], - "sha1": "43d4dec7b3f7190611127a9184ba1b8c7ef95581", + "sha1": "a77f256f44bf9d478cea9072b568053dfdfd7ff6", "gitDir": "test/corpus/repos/javascript", - "sha2": "614d74c2b78fee8293f461aa293c56622049c72b" + "sha2": "aa0b9c6500c4e90003954f42846c897acd910558" } ,{ "testCaseDescription": "javascript-arrow-function-delete-rest-test", @@ -280,8 +271,7 @@ ] } }, - "summary": "Deleted an anonymous(f, g) function", - "tag": "JSONSummary" + "summary": "Deleted an anonymous(f, g) function" } ] }, @@ -290,7 +280,7 @@ "filePaths": [ "arrow-function.js" ], - "sha1": "614d74c2b78fee8293f461aa293c56622049c72b", + "sha1": "aa0b9c6500c4e90003954f42846c897acd910558", "gitDir": "test/corpus/repos/javascript", - "sha2": "9a88415672c0d83242b643e750b77540103e14c1" + "sha2": "5a86b9e93eaf41a19163bf18d160b96b37245ee8" }] diff --git a/test/corpus/diff-summaries/javascript/assignment.json b/test/corpus/diff-summaries/javascript/assignment.json index b67a967a8..7108f5fa4 100644 --- a/test/corpus/diff-summaries/javascript/assignment.json +++ b/test/corpus/diff-summaries/javascript/assignment.json @@ -16,8 +16,7 @@ ] } }, - "summary": "Added the 'x' assignment", - "tag": "JSONSummary" + "summary": "Added the 'x' assignment" } ] }, @@ -26,9 +25,9 @@ "filePaths": [ "assignment.js" ], - "sha1": "e1b8eb2bcd67f643f76a7eb820f49a2ef4f1774c", + "sha1": "a561bcb5c9e49680fd9c162c616048bfa100277a", "gitDir": "test/corpus/repos/javascript", - "sha2": "3a7df001a06d312b1befb24699e3f60a41e07c09" + "sha2": "3305579204370d2000328a15830609cd1a3cc048" } ,{ "testCaseDescription": "javascript-assignment-replacement-insert-test", @@ -48,8 +47,7 @@ ] } }, - "summary": "Added the 'x' assignment", - "tag": "JSONSummary" + "summary": "Added the 'x' assignment" }, { "span": { @@ -64,8 +62,7 @@ ] } }, - "summary": "Added the 'x' assignment", - "tag": "JSONSummary" + "summary": "Added the 'x' assignment" } ] }, @@ -74,9 +71,9 @@ "filePaths": [ "assignment.js" ], - "sha1": "3a7df001a06d312b1befb24699e3f60a41e07c09", + "sha1": "3305579204370d2000328a15830609cd1a3cc048", "gitDir": "test/corpus/repos/javascript", - "sha2": "6142fd5f7cc7d6882b4d2682beb6ab487f37221f" + "sha2": "6df94e140941a17e62fc44b5695a49949169bfb1" } ,{ "testCaseDescription": "javascript-assignment-delete-insert-test", @@ -108,8 +105,7 @@ } ] }, - "summary": "Replaced '1' with '0' in an assignment to x", - "tag": "JSONSummary" + "summary": "Replaced '1' with '0' in an assignment to x" } ] }, @@ -118,9 +114,9 @@ "filePaths": [ "assignment.js" ], - "sha1": "6142fd5f7cc7d6882b4d2682beb6ab487f37221f", + "sha1": "6df94e140941a17e62fc44b5695a49949169bfb1", "gitDir": "test/corpus/repos/javascript", - "sha2": "ccd4b8841a4c1ac1e93e7b6937b085ca9c589f45" + "sha2": "18468291d2bfbfce6c55fd4786eccde87ccb31f0" } ,{ "testCaseDescription": "javascript-assignment-replacement-test", @@ -152,8 +148,7 @@ } ] }, - "summary": "Replaced '0' with '1' in an assignment to x", - "tag": "JSONSummary" + "summary": "Replaced '0' with '1' in an assignment to x" } ] }, @@ -162,9 +157,9 @@ "filePaths": [ "assignment.js" ], - "sha1": "ccd4b8841a4c1ac1e93e7b6937b085ca9c589f45", + "sha1": "18468291d2bfbfce6c55fd4786eccde87ccb31f0", "gitDir": "test/corpus/repos/javascript", - "sha2": "e50c3b804fe956a8d66c615ce341d23949b1e0bc" + "sha2": "f9256802deb7eee30f243cbf5e99688511ae989e" } ,{ "testCaseDescription": "javascript-assignment-delete-replacement-test", @@ -184,8 +179,7 @@ ] } }, - "summary": "Deleted the 'x' assignment", - "tag": "JSONSummary" + "summary": "Deleted the 'x' assignment" }, { "span": { @@ -200,8 +194,7 @@ ] } }, - "summary": "Deleted the 'x' assignment", - "tag": "JSONSummary" + "summary": "Deleted the 'x' assignment" }, { "span": { @@ -216,8 +209,7 @@ ] } }, - "summary": "Added the 'x' assignment", - "tag": "JSONSummary" + "summary": "Added the 'x' assignment" } ] }, @@ -226,9 +218,9 @@ "filePaths": [ "assignment.js" ], - "sha1": "e50c3b804fe956a8d66c615ce341d23949b1e0bc", + "sha1": "f9256802deb7eee30f243cbf5e99688511ae989e", "gitDir": "test/corpus/repos/javascript", - "sha2": "9a82a708b3f1e537ea6580f22e1c61a39c0e56f2" + "sha2": "ce267e2a4a95c57f1ccfbc0fb6d86c846a492757" } ,{ "testCaseDescription": "javascript-assignment-delete-test", @@ -248,8 +240,7 @@ ] } }, - "summary": "Deleted the 'x' assignment", - "tag": "JSONSummary" + "summary": "Deleted the 'x' assignment" } ] }, @@ -258,9 +249,9 @@ "filePaths": [ "assignment.js" ], - "sha1": "9a82a708b3f1e537ea6580f22e1c61a39c0e56f2", + "sha1": "ce267e2a4a95c57f1ccfbc0fb6d86c846a492757", "gitDir": "test/corpus/repos/javascript", - "sha2": "8ca532d1c838722ab652073a5052a0bb58bba456" + "sha2": "d7d26936a69a2962d5ec0b7b30ce6672df042253" } ,{ "testCaseDescription": "javascript-assignment-delete-rest-test", @@ -280,8 +271,7 @@ ] } }, - "summary": "Deleted the 'x' assignment", - "tag": "JSONSummary" + "summary": "Deleted the 'x' assignment" } ] }, @@ -290,7 +280,7 @@ "filePaths": [ "assignment.js" ], - "sha1": "8ca532d1c838722ab652073a5052a0bb58bba456", + "sha1": "d7d26936a69a2962d5ec0b7b30ce6672df042253", "gitDir": "test/corpus/repos/javascript", - "sha2": "db6bbfe82747173a73c33bab9da91003e1fe0634" + "sha2": "3b9571c33eac180e0dcf502ffe6eb68757aa50f2" }] diff --git a/test/corpus/diff-summaries/javascript/bitwise-operator.json b/test/corpus/diff-summaries/javascript/bitwise-operator.json index 5f9ca08e4..10f1156b1 100644 --- a/test/corpus/diff-summaries/javascript/bitwise-operator.json +++ b/test/corpus/diff-summaries/javascript/bitwise-operator.json @@ -16,8 +16,7 @@ ] } }, - "summary": "Added the 'i >> j' bitwise operator", - "tag": "JSONSummary" + "summary": "Added the 'i >> j' bitwise operator" } ] }, @@ -26,9 +25,9 @@ "filePaths": [ "bitwise-operator.js" ], - "sha1": "234b7e78605626501d422c4431c88b50e9e19c3f", + "sha1": "8d428962767d348a3dbaa62c89eab0564badd448", "gitDir": "test/corpus/repos/javascript", - "sha2": "12ac8e040299cccf6336a3001138af774f8fd5de" + "sha2": "ca679b247a491625e6cadc6a0f3c74eb213024bb" } ,{ "testCaseDescription": "javascript-bitwise-operator-replacement-insert-test", @@ -48,8 +47,7 @@ ] } }, - "summary": "Added the 'i >> k' bitwise operator", - "tag": "JSONSummary" + "summary": "Added the 'i >> k' bitwise operator" }, { "span": { @@ -64,8 +62,7 @@ ] } }, - "summary": "Added the 'i >> j' bitwise operator", - "tag": "JSONSummary" + "summary": "Added the 'i >> j' bitwise operator" } ] }, @@ -74,9 +71,9 @@ "filePaths": [ "bitwise-operator.js" ], - "sha1": "12ac8e040299cccf6336a3001138af774f8fd5de", + "sha1": "ca679b247a491625e6cadc6a0f3c74eb213024bb", "gitDir": "test/corpus/repos/javascript", - "sha2": "28a35690a7bb5269f65ed3366cf19eed19b04eb3" + "sha2": "58c64d0c5d074267c5363722ac25292b13333b29" } ,{ "testCaseDescription": "javascript-bitwise-operator-delete-insert-test", @@ -108,8 +105,7 @@ } ] }, - "summary": "Replaced the 'k' identifier with the 'j' identifier", - "tag": "JSONSummary" + "summary": "Replaced the 'k' identifier with the 'j' identifier" } ] }, @@ -118,9 +114,9 @@ "filePaths": [ "bitwise-operator.js" ], - "sha1": "28a35690a7bb5269f65ed3366cf19eed19b04eb3", + "sha1": "58c64d0c5d074267c5363722ac25292b13333b29", "gitDir": "test/corpus/repos/javascript", - "sha2": "caf88ce357d00963864665477ea0261115ba0e82" + "sha2": "3e73c91372d739bfcfceb92cb30be856b0674229" } ,{ "testCaseDescription": "javascript-bitwise-operator-replacement-test", @@ -152,8 +148,7 @@ } ] }, - "summary": "Replaced the 'j' identifier with the 'k' identifier", - "tag": "JSONSummary" + "summary": "Replaced the 'j' identifier with the 'k' identifier" } ] }, @@ -162,9 +157,9 @@ "filePaths": [ "bitwise-operator.js" ], - "sha1": "caf88ce357d00963864665477ea0261115ba0e82", + "sha1": "3e73c91372d739bfcfceb92cb30be856b0674229", "gitDir": "test/corpus/repos/javascript", - "sha2": "04d9d80788f8ec45b6a7fd916aebdb66940d9516" + "sha2": "f5d62f9cf17ccc896f509f6b405805c39f45afc1" } ,{ "testCaseDescription": "javascript-bitwise-operator-delete-replacement-test", @@ -184,8 +179,7 @@ ] } }, - "summary": "Deleted the 'i >> k' bitwise operator", - "tag": "JSONSummary" + "summary": "Deleted the 'i >> k' bitwise operator" }, { "span": { @@ -200,8 +194,7 @@ ] } }, - "summary": "Deleted the 'i >> j' bitwise operator", - "tag": "JSONSummary" + "summary": "Deleted the 'i >> j' bitwise operator" }, { "span": { @@ -216,8 +209,7 @@ ] } }, - "summary": "Added the 'i >> k' bitwise operator", - "tag": "JSONSummary" + "summary": "Added the 'i >> k' bitwise operator" } ] }, @@ -226,9 +218,9 @@ "filePaths": [ "bitwise-operator.js" ], - "sha1": "04d9d80788f8ec45b6a7fd916aebdb66940d9516", + "sha1": "f5d62f9cf17ccc896f509f6b405805c39f45afc1", "gitDir": "test/corpus/repos/javascript", - "sha2": "3b00668eb968387c144b63f111afade1814aa3a7" + "sha2": "db5c1b8fd336475343d489edab9cf0befd5a09d2" } ,{ "testCaseDescription": "javascript-bitwise-operator-delete-test", @@ -248,8 +240,7 @@ ] } }, - "summary": "Deleted the 'i >> j' bitwise operator", - "tag": "JSONSummary" + "summary": "Deleted the 'i >> j' bitwise operator" } ] }, @@ -258,9 +249,9 @@ "filePaths": [ "bitwise-operator.js" ], - "sha1": "3b00668eb968387c144b63f111afade1814aa3a7", + "sha1": "db5c1b8fd336475343d489edab9cf0befd5a09d2", "gitDir": "test/corpus/repos/javascript", - "sha2": "ff907e0620f083698334862f24d9269d1ac43f89" + "sha2": "8b532834c43b74f23cdf9da329f8d7d475acecad" } ,{ "testCaseDescription": "javascript-bitwise-operator-delete-rest-test", @@ -280,8 +271,7 @@ ] } }, - "summary": "Deleted the 'i >> k' bitwise operator", - "tag": "JSONSummary" + "summary": "Deleted the 'i >> k' bitwise operator" } ] }, @@ -290,7 +280,7 @@ "filePaths": [ "bitwise-operator.js" ], - "sha1": "ff907e0620f083698334862f24d9269d1ac43f89", + "sha1": "8b532834c43b74f23cdf9da329f8d7d475acecad", "gitDir": "test/corpus/repos/javascript", - "sha2": "d3b83b525c7e185792b6284b8c0b23dbce07fa7e" + "sha2": "1e420171d01e2dca638a5f134f88454bd64d79ae" }] diff --git a/test/corpus/diff-summaries/javascript/boolean-operator.json b/test/corpus/diff-summaries/javascript/boolean-operator.json index e719fedf8..c57164b1b 100644 --- a/test/corpus/diff-summaries/javascript/boolean-operator.json +++ b/test/corpus/diff-summaries/javascript/boolean-operator.json @@ -16,8 +16,7 @@ ] } }, - "summary": "Added the 'i || j' boolean operator", - "tag": "JSONSummary" + "summary": "Added the 'i || j' boolean operator" } ] }, @@ -26,9 +25,9 @@ "filePaths": [ "boolean-operator.js" ], - "sha1": "81b6988e6543884fa895f07a06283ca091f49afb", + "sha1": "faaff0e5dd144b090a540e45f9a534c1cceb3ad1", "gitDir": "test/corpus/repos/javascript", - "sha2": "77c4304f467e33c59a93a93a9cd1e5e1ebf7809b" + "sha2": "d6e10ec4014abbcb6b6b338b66eb6f995a232d67" } ,{ "testCaseDescription": "javascript-boolean-operator-replacement-insert-test", @@ -48,8 +47,7 @@ ] } }, - "summary": "Added the 'i && j' boolean operator", - "tag": "JSONSummary" + "summary": "Added the 'i && j' boolean operator" }, { "span": { @@ -64,8 +62,7 @@ ] } }, - "summary": "Added the 'i || j' boolean operator", - "tag": "JSONSummary" + "summary": "Added the 'i || j' boolean operator" } ] }, @@ -74,9 +71,9 @@ "filePaths": [ "boolean-operator.js" ], - "sha1": "77c4304f467e33c59a93a93a9cd1e5e1ebf7809b", + "sha1": "d6e10ec4014abbcb6b6b338b66eb6f995a232d67", "gitDir": "test/corpus/repos/javascript", - "sha2": "04da46027e8e42577cf51f664a641af1473ea21b" + "sha2": "b09e021bfef5da21754a88b63145c80bc8613308" } ,{ "testCaseDescription": "javascript-boolean-operator-delete-insert-test", @@ -87,9 +84,9 @@ "filePaths": [ "boolean-operator.js" ], - "sha1": "04da46027e8e42577cf51f664a641af1473ea21b", + "sha1": "b09e021bfef5da21754a88b63145c80bc8613308", "gitDir": "test/corpus/repos/javascript", - "sha2": "2144b6fdcd32aa805f9a548e8c774d4b0d78211e" + "sha2": "3958808a1800344b293b9bc9d432b68041ff5d87" } ,{ "testCaseDescription": "javascript-boolean-operator-replacement-test", @@ -100,9 +97,9 @@ "filePaths": [ "boolean-operator.js" ], - "sha1": "2144b6fdcd32aa805f9a548e8c774d4b0d78211e", + "sha1": "3958808a1800344b293b9bc9d432b68041ff5d87", "gitDir": "test/corpus/repos/javascript", - "sha2": "cab2550c31bd9e3b9ca409155d875b9c34a96396" + "sha2": "1625b72ec355c939829455d5397838e0328e6f39" } ,{ "testCaseDescription": "javascript-boolean-operator-delete-replacement-test", @@ -122,8 +119,7 @@ ] } }, - "summary": "Deleted the 'i && j' boolean operator", - "tag": "JSONSummary" + "summary": "Deleted the 'i && j' boolean operator" } ] }, @@ -132,9 +128,9 @@ "filePaths": [ "boolean-operator.js" ], - "sha1": "cab2550c31bd9e3b9ca409155d875b9c34a96396", + "sha1": "1625b72ec355c939829455d5397838e0328e6f39", "gitDir": "test/corpus/repos/javascript", - "sha2": "d255d477f62bb73de5039084ffd0afecbb5d500c" + "sha2": "a4f53d533f7359d95917a22771bc125f137dd311" } ,{ "testCaseDescription": "javascript-boolean-operator-delete-test", @@ -154,8 +150,7 @@ ] } }, - "summary": "Deleted the 'i || j' boolean operator", - "tag": "JSONSummary" + "summary": "Deleted the 'i || j' boolean operator" } ] }, @@ -164,9 +159,9 @@ "filePaths": [ "boolean-operator.js" ], - "sha1": "d255d477f62bb73de5039084ffd0afecbb5d500c", + "sha1": "a4f53d533f7359d95917a22771bc125f137dd311", "gitDir": "test/corpus/repos/javascript", - "sha2": "ec883a059891f976a9050e6b9100135dbe5cabee" + "sha2": "a1e71d859792a4497b9438fe57d0b17847b53184" } ,{ "testCaseDescription": "javascript-boolean-operator-delete-rest-test", @@ -186,8 +181,7 @@ ] } }, - "summary": "Deleted the 'i && j' boolean operator", - "tag": "JSONSummary" + "summary": "Deleted the 'i && j' boolean operator" } ] }, @@ -196,7 +190,7 @@ "filePaths": [ "boolean-operator.js" ], - "sha1": "ec883a059891f976a9050e6b9100135dbe5cabee", + "sha1": "a1e71d859792a4497b9438fe57d0b17847b53184", "gitDir": "test/corpus/repos/javascript", - "sha2": "35c3545e63b37ef12af64bbc9bafaf502a95db29" + "sha2": "e1dc429edadeaaff5ea72c53fefab478501bdc07" }] diff --git a/test/corpus/diff-summaries/javascript/chained-callbacks.json b/test/corpus/diff-summaries/javascript/chained-callbacks.json index e72a6b0d5..1d7daa334 100644 --- a/test/corpus/diff-summaries/javascript/chained-callbacks.json +++ b/test/corpus/diff-summaries/javascript/chained-callbacks.json @@ -16,8 +16,7 @@ ] } }, - "summary": "Added the 'this.map(…)' method call", - "tag": "JSONSummary" + "summary": "Added the 'this.map(…)' method call" } ] }, @@ -26,9 +25,9 @@ "filePaths": [ "chained-callbacks.js" ], - "sha1": "9805a53f9fb8f6cd969d07ef2eeec2250fd12d04", + "sha1": "13cc6ff656f24edfd27ef7cdbbf33198c415c712", "gitDir": "test/corpus/repos/javascript", - "sha2": "95c5995bf1d9fd3208a872cd598032cece4a8bac" + "sha2": "ba8ce3f9c7e869e67a2b1d9ad2b98ea18b349916" } ,{ "testCaseDescription": "javascript-chained-callbacks-replacement-insert-test", @@ -48,8 +47,7 @@ ] } }, - "summary": "Added the 'this.reduce(…)' method call", - "tag": "JSONSummary" + "summary": "Added the 'this.reduce(…)' method call" }, { "span": { @@ -64,8 +62,7 @@ ] } }, - "summary": "Added the 'this.map(…)' method call", - "tag": "JSONSummary" + "summary": "Added the 'this.map(…)' method call" } ] }, @@ -74,9 +71,9 @@ "filePaths": [ "chained-callbacks.js" ], - "sha1": "95c5995bf1d9fd3208a872cd598032cece4a8bac", + "sha1": "ba8ce3f9c7e869e67a2b1d9ad2b98ea18b349916", "gitDir": "test/corpus/repos/javascript", - "sha2": "4b97bdc99bdd0ff6bb811ab647482f93444203d7" + "sha2": "d0276aee638ca8e24ee6d91a339544df8fb7eda3" } ,{ "testCaseDescription": "javascript-chained-callbacks-delete-insert-test", @@ -108,8 +105,7 @@ } ] }, - "summary": "Replaced the 'reduce' identifier with the 'map' identifier in the this.map(…) method call", - "tag": "JSONSummary" + "summary": "Replaced the 'reduce' identifier with the 'map' identifier in the this.map(…) method call" }, { "span": { @@ -136,8 +132,7 @@ } ] }, - "summary": "Replaced the 'b' identifier with the 'a' identifier in the this.map(…) method call", - "tag": "JSONSummary" + "summary": "Replaced the 'b' identifier with the 'a' identifier in the this.map(…) method call" }, { "span": { @@ -164,8 +159,7 @@ } ] }, - "summary": "Replaced the 'a' identifier with the 'b' identifier in the this.map(…) method call", - "tag": "JSONSummary" + "summary": "Replaced the 'a' identifier with the 'b' identifier in the this.map(…) method call" } ] }, @@ -174,9 +168,9 @@ "filePaths": [ "chained-callbacks.js" ], - "sha1": "4b97bdc99bdd0ff6bb811ab647482f93444203d7", + "sha1": "d0276aee638ca8e24ee6d91a339544df8fb7eda3", "gitDir": "test/corpus/repos/javascript", - "sha2": "e925672c3d607a47dd28821be89fc163547f317a" + "sha2": "85f3727c68cea10835a214942b66e4d430b73a62" } ,{ "testCaseDescription": "javascript-chained-callbacks-replacement-test", @@ -208,8 +202,7 @@ } ] }, - "summary": "Replaced the 'map' identifier with the 'reduce' identifier in the this.reduce(…) method call", - "tag": "JSONSummary" + "summary": "Replaced the 'map' identifier with the 'reduce' identifier in the this.reduce(…) method call" }, { "span": { @@ -236,8 +229,7 @@ } ] }, - "summary": "Replaced the 'a' identifier with the 'b' identifier in the this.reduce(…) method call", - "tag": "JSONSummary" + "summary": "Replaced the 'a' identifier with the 'b' identifier in the this.reduce(…) method call" }, { "span": { @@ -264,8 +256,7 @@ } ] }, - "summary": "Replaced the 'b' identifier with the 'a' identifier in the this.reduce(…) method call", - "tag": "JSONSummary" + "summary": "Replaced the 'b' identifier with the 'a' identifier in the this.reduce(…) method call" } ] }, @@ -274,9 +265,9 @@ "filePaths": [ "chained-callbacks.js" ], - "sha1": "e925672c3d607a47dd28821be89fc163547f317a", + "sha1": "85f3727c68cea10835a214942b66e4d430b73a62", "gitDir": "test/corpus/repos/javascript", - "sha2": "8f1ee6a59a82c0aa8e951dd4b2865f8105c4b9e4" + "sha2": "0726997ed14f742f2e3ad23f575cb88aaa5f4b98" } ,{ "testCaseDescription": "javascript-chained-callbacks-delete-replacement-test", @@ -296,8 +287,7 @@ ] } }, - "summary": "Deleted the 'this.reduce(…)' method call", - "tag": "JSONSummary" + "summary": "Deleted the 'this.reduce(…)' method call" }, { "span": { @@ -312,8 +302,7 @@ ] } }, - "summary": "Deleted the 'this.map(…)' method call", - "tag": "JSONSummary" + "summary": "Deleted the 'this.map(…)' method call" }, { "span": { @@ -328,8 +317,7 @@ ] } }, - "summary": "Added the 'this.reduce(…)' method call", - "tag": "JSONSummary" + "summary": "Added the 'this.reduce(…)' method call" } ] }, @@ -338,9 +326,9 @@ "filePaths": [ "chained-callbacks.js" ], - "sha1": "8f1ee6a59a82c0aa8e951dd4b2865f8105c4b9e4", + "sha1": "0726997ed14f742f2e3ad23f575cb88aaa5f4b98", "gitDir": "test/corpus/repos/javascript", - "sha2": "fca34a1451c2b8708049c924710c971127d9efc0" + "sha2": "db6518a336784be0d8565f2ff963767dffbe22a0" } ,{ "testCaseDescription": "javascript-chained-callbacks-delete-test", @@ -360,8 +348,7 @@ ] } }, - "summary": "Deleted the 'this.map(…)' method call", - "tag": "JSONSummary" + "summary": "Deleted the 'this.map(…)' method call" } ] }, @@ -370,9 +357,9 @@ "filePaths": [ "chained-callbacks.js" ], - "sha1": "fca34a1451c2b8708049c924710c971127d9efc0", + "sha1": "db6518a336784be0d8565f2ff963767dffbe22a0", "gitDir": "test/corpus/repos/javascript", - "sha2": "820ff2e5b738c2a4c6b67bb00137825db09eaf54" + "sha2": "f150e07a04ef679de98aa6a19c4e4d534230f7cc" } ,{ "testCaseDescription": "javascript-chained-callbacks-delete-rest-test", @@ -392,8 +379,7 @@ ] } }, - "summary": "Deleted the 'this.reduce(…)' method call", - "tag": "JSONSummary" + "summary": "Deleted the 'this.reduce(…)' method call" } ] }, @@ -402,7 +388,7 @@ "filePaths": [ "chained-callbacks.js" ], - "sha1": "820ff2e5b738c2a4c6b67bb00137825db09eaf54", + "sha1": "f150e07a04ef679de98aa6a19c4e4d534230f7cc", "gitDir": "test/corpus/repos/javascript", - "sha2": "d1e7f56a86f0ad76a52e486579b7319c4da64d38" + "sha2": "6b7dd7946b24ba4d49e866944f3bef05c4e948a5" }] diff --git a/test/corpus/diff-summaries/javascript/chained-property-access.json b/test/corpus/diff-summaries/javascript/chained-property-access.json index 552a4adb1..97e2e0513 100644 --- a/test/corpus/diff-summaries/javascript/chained-property-access.json +++ b/test/corpus/diff-summaries/javascript/chained-property-access.json @@ -16,8 +16,7 @@ ] } }, - "summary": "Added the 'returned.promise().done(…).fail(…)' return statement", - "tag": "JSONSummary" + "summary": "Added the 'returned.promise().done(…).fail(…)' return statement" } ] }, @@ -26,9 +25,9 @@ "filePaths": [ "chained-property-access.js" ], - "sha1": "1e0859960bebec7c346191192b74d0625ae68f54", + "sha1": "d18ce614bfee6bf352af0ace4d200778e8fb4eaf", "gitDir": "test/corpus/repos/javascript", - "sha2": "607fd3f3d13592c0bf22ffd2ad1395c759a9ac9c" + "sha2": "dd59773bcf047bb1a9af4a67c57647d6638492e9" } ,{ "testCaseDescription": "javascript-chained-property-access-replacement-insert-test", @@ -48,8 +47,7 @@ ] } }, - "summary": "Added the 'returned.promise().done(…).fail(…)' return statement", - "tag": "JSONSummary" + "summary": "Added the 'returned.promise().done(…).fail(…)' return statement" }, { "span": { @@ -64,8 +62,7 @@ ] } }, - "summary": "Added the 'returned.promise().done(…).fail(…)' return statement", - "tag": "JSONSummary" + "summary": "Added the 'returned.promise().done(…).fail(…)' return statement" } ] }, @@ -74,9 +71,9 @@ "filePaths": [ "chained-property-access.js" ], - "sha1": "607fd3f3d13592c0bf22ffd2ad1395c759a9ac9c", + "sha1": "dd59773bcf047bb1a9af4a67c57647d6638492e9", "gitDir": "test/corpus/repos/javascript", - "sha2": "bfbb22ba2d321e4b458857e6e6e053d387bd744e" + "sha2": "2a35d54700748513ec68ec03f7f5047fac3c1d91" } ,{ "testCaseDescription": "javascript-chained-property-access-delete-insert-test", @@ -108,8 +105,7 @@ } ] }, - "summary": "Replaced the 'otherDefer' identifier with the 'newDefer' identifier in the returned.promise().done(…) method call", - "tag": "JSONSummary" + "summary": "Replaced the 'otherDefer' identifier with the 'newDefer' identifier in the returned.promise().done(…) method call" }, { "span": { @@ -136,8 +132,7 @@ } ] }, - "summary": "Replaced the 'otherDefer' identifier with the 'newDefer' identifier in the returned.promise().done(…).fail(…) method call", - "tag": "JSONSummary" + "summary": "Replaced the 'otherDefer' identifier with the 'newDefer' identifier in the returned.promise().done(…).fail(…) method call" } ] }, @@ -146,9 +141,9 @@ "filePaths": [ "chained-property-access.js" ], - "sha1": "bfbb22ba2d321e4b458857e6e6e053d387bd744e", + "sha1": "2a35d54700748513ec68ec03f7f5047fac3c1d91", "gitDir": "test/corpus/repos/javascript", - "sha2": "f8c579de58d41201e75fc6ef898bb19612485b74" + "sha2": "56c9c8d996ec55dc343c370027e921250704cda2" } ,{ "testCaseDescription": "javascript-chained-property-access-replacement-test", @@ -180,8 +175,7 @@ } ] }, - "summary": "Replaced the 'newDefer' identifier with the 'otherDefer' identifier in the returned.promise().done(…) method call", - "tag": "JSONSummary" + "summary": "Replaced the 'newDefer' identifier with the 'otherDefer' identifier in the returned.promise().done(…) method call" }, { "span": { @@ -208,8 +202,7 @@ } ] }, - "summary": "Replaced the 'newDefer' identifier with the 'otherDefer' identifier in the returned.promise().done(…).fail(…) method call", - "tag": "JSONSummary" + "summary": "Replaced the 'newDefer' identifier with the 'otherDefer' identifier in the returned.promise().done(…).fail(…) method call" } ] }, @@ -218,9 +211,9 @@ "filePaths": [ "chained-property-access.js" ], - "sha1": "f8c579de58d41201e75fc6ef898bb19612485b74", + "sha1": "56c9c8d996ec55dc343c370027e921250704cda2", "gitDir": "test/corpus/repos/javascript", - "sha2": "500274ded0883d60ed5e9137cde2a9c5ec057646" + "sha2": "e27981a5a59769ef1b5d5b7d793413ea27df7d90" } ,{ "testCaseDescription": "javascript-chained-property-access-delete-replacement-test", @@ -240,8 +233,7 @@ ] } }, - "summary": "Deleted the 'returned.promise().done(…).fail(…)' return statement", - "tag": "JSONSummary" + "summary": "Deleted the 'returned.promise().done(…).fail(…)' return statement" }, { "span": { @@ -256,8 +248,7 @@ ] } }, - "summary": "Deleted the 'returned.promise().done(…).fail(…)' return statement", - "tag": "JSONSummary" + "summary": "Deleted the 'returned.promise().done(…).fail(…)' return statement" }, { "span": { @@ -272,8 +263,7 @@ ] } }, - "summary": "Added the 'returned.promise().done(…).fail(…)' return statement", - "tag": "JSONSummary" + "summary": "Added the 'returned.promise().done(…).fail(…)' return statement" } ] }, @@ -282,9 +272,9 @@ "filePaths": [ "chained-property-access.js" ], - "sha1": "500274ded0883d60ed5e9137cde2a9c5ec057646", + "sha1": "e27981a5a59769ef1b5d5b7d793413ea27df7d90", "gitDir": "test/corpus/repos/javascript", - "sha2": "c4b82844d26c3b49ff4ad0bb6908e89ff58e87f1" + "sha2": "de1aa8b591a0eba6fc463f536626ac1ea4cba935" } ,{ "testCaseDescription": "javascript-chained-property-access-delete-test", @@ -304,8 +294,7 @@ ] } }, - "summary": "Deleted the 'returned.promise().done(…).fail(…)' return statement", - "tag": "JSONSummary" + "summary": "Deleted the 'returned.promise().done(…).fail(…)' return statement" } ] }, @@ -314,9 +303,9 @@ "filePaths": [ "chained-property-access.js" ], - "sha1": "c4b82844d26c3b49ff4ad0bb6908e89ff58e87f1", + "sha1": "de1aa8b591a0eba6fc463f536626ac1ea4cba935", "gitDir": "test/corpus/repos/javascript", - "sha2": "1a601394ffbc287695bbf2b63d5e85d1b9ba66dd" + "sha2": "4e04595fb1ccf12f0affa9d40a57d54e40b1bb2f" } ,{ "testCaseDescription": "javascript-chained-property-access-delete-rest-test", @@ -336,8 +325,7 @@ ] } }, - "summary": "Deleted the 'returned.promise().done(…).fail(…)' return statement", - "tag": "JSONSummary" + "summary": "Deleted the 'returned.promise().done(…).fail(…)' return statement" } ] }, @@ -346,7 +334,7 @@ "filePaths": [ "chained-property-access.js" ], - "sha1": "1a601394ffbc287695bbf2b63d5e85d1b9ba66dd", + "sha1": "4e04595fb1ccf12f0affa9d40a57d54e40b1bb2f", "gitDir": "test/corpus/repos/javascript", - "sha2": "e2ad5d3fafb90d720b3c803892c914529086848a" + "sha2": "0ae29a51ae1d4aa57c5239393081efaf63982b12" }] diff --git a/test/corpus/diff-summaries/javascript/class.json b/test/corpus/diff-summaries/javascript/class.json index 0f7a99db5..05e58aaff 100644 --- a/test/corpus/diff-summaries/javascript/class.json +++ b/test/corpus/diff-summaries/javascript/class.json @@ -16,8 +16,7 @@ ] } }, - "summary": "Added the 'Foo' class", - "tag": "JSONSummary" + "summary": "Added the 'Foo' class" } ] }, @@ -26,9 +25,9 @@ "filePaths": [ "class.js" ], - "sha1": "19a0f5ed94699f179f887755095f2b6bd484ba1b", + "sha1": "d17a2b38a62067233adf6ee07cd8e79c78862e83", "gitDir": "test/corpus/repos/javascript", - "sha2": "f83f2944c43ab1c3a311114018bc9def1a08ef2c" + "sha2": "b3c38949d2744c30985b401eeb4a8d5968214038" } ,{ "testCaseDescription": "javascript-class-replacement-insert-test", @@ -48,8 +47,7 @@ ] } }, - "summary": "Added the 'Foo' class", - "tag": "JSONSummary" + "summary": "Added the 'Foo' class" }, { "span": { @@ -64,8 +62,7 @@ ] } }, - "summary": "Added the 'Foo' class", - "tag": "JSONSummary" + "summary": "Added the 'Foo' class" } ] }, @@ -74,9 +71,9 @@ "filePaths": [ "class.js" ], - "sha1": "f83f2944c43ab1c3a311114018bc9def1a08ef2c", + "sha1": "b3c38949d2744c30985b401eeb4a8d5968214038", "gitDir": "test/corpus/repos/javascript", - "sha2": "9c20b127c193a62b80eda6b277bb7a909e7b761a" + "sha2": "7b2f9b1099f78cc3f7e78764536742adcf9c371f" } ,{ "testCaseDescription": "javascript-class-delete-insert-test", @@ -108,8 +105,7 @@ } ] }, - "summary": "Replaced the 'foo' identifier with the 'one' identifier in the one method of the 'Foo' class", - "tag": "JSONSummary" + "summary": "Replaced the 'foo' identifier with the 'one' identifier in the one method of the 'Foo' class" }, { "span": { @@ -136,8 +132,7 @@ } ] }, - "summary": "Replaced the 'bar' identifier with the 'two' identifier in the two method of the 'Foo' class", - "tag": "JSONSummary" + "summary": "Replaced the 'bar' identifier with the 'two' identifier in the two method of the 'Foo' class" }, { "span": { @@ -164,8 +159,7 @@ } ] }, - "summary": "Replaced the 'baz' identifier with the 'three' identifier in the three method of the 'Foo' class", - "tag": "JSONSummary" + "summary": "Replaced the 'baz' identifier with the 'three' identifier in the three method of the 'Foo' class" } ] }, @@ -174,9 +168,9 @@ "filePaths": [ "class.js" ], - "sha1": "9c20b127c193a62b80eda6b277bb7a909e7b761a", + "sha1": "7b2f9b1099f78cc3f7e78764536742adcf9c371f", "gitDir": "test/corpus/repos/javascript", - "sha2": "f89babcecc359be4cc277d1c9970a8deaa3e8fe6" + "sha2": "c6b41195ff78d15375ecad210138f106b491c397" } ,{ "testCaseDescription": "javascript-class-replacement-test", @@ -208,8 +202,7 @@ } ] }, - "summary": "Replaced the 'one' identifier with the 'foo' identifier in the foo method of the 'Foo' class", - "tag": "JSONSummary" + "summary": "Replaced the 'one' identifier with the 'foo' identifier in the foo method of the 'Foo' class" }, { "span": { @@ -236,8 +229,7 @@ } ] }, - "summary": "Replaced the 'two' identifier with the 'bar' identifier in the bar method of the 'Foo' class", - "tag": "JSONSummary" + "summary": "Replaced the 'two' identifier with the 'bar' identifier in the bar method of the 'Foo' class" }, { "span": { @@ -264,8 +256,7 @@ } ] }, - "summary": "Replaced the 'three' identifier with the 'baz' identifier in the baz method of the 'Foo' class", - "tag": "JSONSummary" + "summary": "Replaced the 'three' identifier with the 'baz' identifier in the baz method of the 'Foo' class" } ] }, @@ -274,9 +265,9 @@ "filePaths": [ "class.js" ], - "sha1": "f89babcecc359be4cc277d1c9970a8deaa3e8fe6", + "sha1": "c6b41195ff78d15375ecad210138f106b491c397", "gitDir": "test/corpus/repos/javascript", - "sha2": "db12f186575ae386af489e213608fa3a80773747" + "sha2": "72d9f8358863431e6f9ded0aed0877dd974afd24" } ,{ "testCaseDescription": "javascript-class-delete-replacement-test", @@ -296,8 +287,7 @@ ] } }, - "summary": "Deleted the 'Foo' class", - "tag": "JSONSummary" + "summary": "Deleted the 'Foo' class" }, { "span": { @@ -312,8 +302,7 @@ ] } }, - "summary": "Deleted the 'Foo' class", - "tag": "JSONSummary" + "summary": "Deleted the 'Foo' class" }, { "span": { @@ -328,8 +317,7 @@ ] } }, - "summary": "Added the 'Foo' class", - "tag": "JSONSummary" + "summary": "Added the 'Foo' class" } ] }, @@ -338,9 +326,9 @@ "filePaths": [ "class.js" ], - "sha1": "db12f186575ae386af489e213608fa3a80773747", + "sha1": "72d9f8358863431e6f9ded0aed0877dd974afd24", "gitDir": "test/corpus/repos/javascript", - "sha2": "feb3a4cf1baa84520130badfe96c139a0d6dc94d" + "sha2": "41fbfe38957d1857423e745ab7cc6af99470141b" } ,{ "testCaseDescription": "javascript-class-delete-test", @@ -360,8 +348,7 @@ ] } }, - "summary": "Deleted the 'Foo' class", - "tag": "JSONSummary" + "summary": "Deleted the 'Foo' class" } ] }, @@ -370,9 +357,9 @@ "filePaths": [ "class.js" ], - "sha1": "feb3a4cf1baa84520130badfe96c139a0d6dc94d", + "sha1": "41fbfe38957d1857423e745ab7cc6af99470141b", "gitDir": "test/corpus/repos/javascript", - "sha2": "a41d47574ddcd9f4427ab581e5651ed26ffc1b9d" + "sha2": "741d75c2f76964d86375e18fb7154936b746410a" } ,{ "testCaseDescription": "javascript-class-delete-rest-test", @@ -392,8 +379,7 @@ ] } }, - "summary": "Deleted the 'Foo' class", - "tag": "JSONSummary" + "summary": "Deleted the 'Foo' class" } ] }, @@ -402,7 +388,7 @@ "filePaths": [ "class.js" ], - "sha1": "a41d47574ddcd9f4427ab581e5651ed26ffc1b9d", + "sha1": "741d75c2f76964d86375e18fb7154936b746410a", "gitDir": "test/corpus/repos/javascript", - "sha2": "395c6eece5c8b6aa98613ca7569ddd88f70d7988" + "sha2": "e3605367f3839bdb67e5ef00ea3be0afdd7d72aa" }] diff --git a/test/corpus/diff-summaries/javascript/comma-operator.json b/test/corpus/diff-summaries/javascript/comma-operator.json index 742fde82d..1d00da3aa 100644 --- a/test/corpus/diff-summaries/javascript/comma-operator.json +++ b/test/corpus/diff-summaries/javascript/comma-operator.json @@ -16,8 +16,7 @@ ] } }, - "summary": "Added the 'a' assignment", - "tag": "JSONSummary" + "summary": "Added the 'a' assignment" }, { "span": { @@ -32,8 +31,7 @@ ] } }, - "summary": "Added the 'b' assignment", - "tag": "JSONSummary" + "summary": "Added the 'b' assignment" } ] }, @@ -42,9 +40,9 @@ "filePaths": [ "comma-operator.js" ], - "sha1": "c376ba3379a36f234ec18e27404102b3ec9c0794", + "sha1": "93d092557623a476afac612ad5053ab3e5a63d69", "gitDir": "test/corpus/repos/javascript", - "sha2": "31e90b6b1c5c3dc917da063eaf26d247b75b5c46" + "sha2": "925d714e520d236f773fd66415cc85d568567c28" } ,{ "testCaseDescription": "javascript-comma-operator-replacement-insert-test", @@ -64,8 +62,7 @@ ] } }, - "summary": "Added the 'c' assignment", - "tag": "JSONSummary" + "summary": "Added the 'c' assignment" }, { "span": { @@ -80,8 +77,7 @@ ] } }, - "summary": "Added the 'a' assignment", - "tag": "JSONSummary" + "summary": "Added the 'a' assignment" }, { "span": { @@ -96,8 +92,7 @@ ] } }, - "summary": "Added the 'b' assignment", - "tag": "JSONSummary" + "summary": "Added the 'b' assignment" } ] }, @@ -106,9 +101,9 @@ "filePaths": [ "comma-operator.js" ], - "sha1": "31e90b6b1c5c3dc917da063eaf26d247b75b5c46", + "sha1": "925d714e520d236f773fd66415cc85d568567c28", "gitDir": "test/corpus/repos/javascript", - "sha2": "80531ffeb669b96cf79ad6c9ad2324d4c238e2a4" + "sha2": "62b94cc1adb6550f6cc3d5487fa0b2fb98f7f64a" } ,{ "testCaseDescription": "javascript-comma-operator-delete-insert-test", @@ -128,8 +123,7 @@ ] } }, - "summary": "Added the 'a' assignment", - "tag": "JSONSummary" + "summary": "Added the 'a' assignment" }, { "span": { @@ -144,8 +138,7 @@ ] } }, - "summary": "Added the 'b' assignment", - "tag": "JSONSummary" + "summary": "Added the 'b' assignment" }, { "span": { @@ -160,8 +153,7 @@ ] } }, - "summary": "Deleted the 'c' assignment", - "tag": "JSONSummary" + "summary": "Deleted the 'c' assignment" } ] }, @@ -170,9 +162,9 @@ "filePaths": [ "comma-operator.js" ], - "sha1": "80531ffeb669b96cf79ad6c9ad2324d4c238e2a4", + "sha1": "62b94cc1adb6550f6cc3d5487fa0b2fb98f7f64a", "gitDir": "test/corpus/repos/javascript", - "sha2": "8a61a54a5e569eb053d0bbdf9f2aa8093b66ffdc" + "sha2": "a4b777d2bcbeb98a22c575be5aed21065915ca25" } ,{ "testCaseDescription": "javascript-comma-operator-replacement-test", @@ -192,8 +184,7 @@ ] } }, - "summary": "Added the 'c' assignment", - "tag": "JSONSummary" + "summary": "Added the 'c' assignment" }, { "span": { @@ -208,8 +199,7 @@ ] } }, - "summary": "Deleted the 'a' assignment", - "tag": "JSONSummary" + "summary": "Deleted the 'a' assignment" }, { "span": { @@ -224,8 +214,7 @@ ] } }, - "summary": "Deleted the 'b' assignment", - "tag": "JSONSummary" + "summary": "Deleted the 'b' assignment" } ] }, @@ -234,9 +223,9 @@ "filePaths": [ "comma-operator.js" ], - "sha1": "8a61a54a5e569eb053d0bbdf9f2aa8093b66ffdc", + "sha1": "a4b777d2bcbeb98a22c575be5aed21065915ca25", "gitDir": "test/corpus/repos/javascript", - "sha2": "4de76b87e19fa641bbde82250f5c1448582adde0" + "sha2": "0044976b6fe9bc1a88363179b05c9164d020d6e0" } ,{ "testCaseDescription": "javascript-comma-operator-delete-replacement-test", @@ -256,8 +245,7 @@ ] } }, - "summary": "Deleted the 'c' assignment", - "tag": "JSONSummary" + "summary": "Deleted the 'c' assignment" }, { "span": { @@ -272,8 +260,7 @@ ] } }, - "summary": "Deleted the 'a' assignment", - "tag": "JSONSummary" + "summary": "Deleted the 'a' assignment" }, { "span": { @@ -288,8 +275,7 @@ ] } }, - "summary": "Deleted the 'b' assignment", - "tag": "JSONSummary" + "summary": "Deleted the 'b' assignment" }, { "span": { @@ -304,8 +290,7 @@ ] } }, - "summary": "Added the 'c' assignment", - "tag": "JSONSummary" + "summary": "Added the 'c' assignment" } ] }, @@ -314,9 +299,9 @@ "filePaths": [ "comma-operator.js" ], - "sha1": "4de76b87e19fa641bbde82250f5c1448582adde0", + "sha1": "0044976b6fe9bc1a88363179b05c9164d020d6e0", "gitDir": "test/corpus/repos/javascript", - "sha2": "358a64dfe4454828ab1cd7632ea33aabf8791031" + "sha2": "437b6ad23f402553fa54eabc101e1009fe7e90f7" } ,{ "testCaseDescription": "javascript-comma-operator-delete-test", @@ -336,8 +321,7 @@ ] } }, - "summary": "Deleted the 'a' assignment", - "tag": "JSONSummary" + "summary": "Deleted the 'a' assignment" }, { "span": { @@ -352,8 +336,7 @@ ] } }, - "summary": "Deleted the 'b' assignment", - "tag": "JSONSummary" + "summary": "Deleted the 'b' assignment" } ] }, @@ -362,9 +345,9 @@ "filePaths": [ "comma-operator.js" ], - "sha1": "358a64dfe4454828ab1cd7632ea33aabf8791031", + "sha1": "437b6ad23f402553fa54eabc101e1009fe7e90f7", "gitDir": "test/corpus/repos/javascript", - "sha2": "c7bc8d4656be920af42145c1ff818668ad25bcaa" + "sha2": "cf7b30999c40f435c936f1ca0dafda480f24624b" } ,{ "testCaseDescription": "javascript-comma-operator-delete-rest-test", @@ -384,8 +367,7 @@ ] } }, - "summary": "Deleted the 'c' assignment", - "tag": "JSONSummary" + "summary": "Deleted the 'c' assignment" } ] }, @@ -394,7 +376,7 @@ "filePaths": [ "comma-operator.js" ], - "sha1": "c7bc8d4656be920af42145c1ff818668ad25bcaa", + "sha1": "cf7b30999c40f435c936f1ca0dafda480f24624b", "gitDir": "test/corpus/repos/javascript", - "sha2": "2a1ddb9a8c6d84924131fb18113f31eeade50718" + "sha2": "b0f399ee205a0929d5082717bdff84b949f064b3" }] diff --git a/test/corpus/diff-summaries/javascript/comment.json b/test/corpus/diff-summaries/javascript/comment.json index c17239fac..94ac098c7 100644 --- a/test/corpus/diff-summaries/javascript/comment.json +++ b/test/corpus/diff-summaries/javascript/comment.json @@ -16,8 +16,7 @@ ] } }, - "summary": "Added the '// This is a property' comment", - "tag": "JSONSummary" + "summary": "Added the '// This is a property' comment" } ] }, @@ -26,9 +25,9 @@ "filePaths": [ "comment.js" ], - "sha1": "9ed8066a32b8ac3bc857ec9ffb963f12322f5224", + "sha1": "9966bf3346783a8e39f77cc3b61f8c24f851b0ed", "gitDir": "test/corpus/repos/javascript", - "sha2": "cbdd13e093a8640ad08ec76174b68cf07600c1ea" + "sha2": "0b532cc7ac2078fb6421efad2fba431eebf8b079" } ,{ "testCaseDescription": "javascript-comment-replacement-insert-test", @@ -48,8 +47,7 @@ ] } }, - "summary": "Added the '/*\n * This is a method\n*/' comment", - "tag": "JSONSummary" + "summary": "Added the '/*\n * This is a method\n*/' comment" }, { "span": { @@ -64,8 +62,7 @@ ] } }, - "summary": "Added the '// This is a property' comment", - "tag": "JSONSummary" + "summary": "Added the '// This is a property' comment" } ] }, @@ -74,9 +71,9 @@ "filePaths": [ "comment.js" ], - "sha1": "cbdd13e093a8640ad08ec76174b68cf07600c1ea", + "sha1": "0b532cc7ac2078fb6421efad2fba431eebf8b079", "gitDir": "test/corpus/repos/javascript", - "sha2": "f5a91dac7a4f5f86c7a7cf2c69c5e988fb408712" + "sha2": "22391ec032d8cf2569c2c79daf9edd535fd5ae1f" } ,{ "testCaseDescription": "javascript-comment-delete-insert-test", @@ -108,8 +105,7 @@ } ] }, - "summary": "Replaced the '/*\n * This is a method\n*/' comment with the '// This is a property' comment", - "tag": "JSONSummary" + "summary": "Replaced the '/*\n * This is a method\n*/' comment with the '// This is a property' comment" } ] }, @@ -118,9 +114,9 @@ "filePaths": [ "comment.js" ], - "sha1": "f5a91dac7a4f5f86c7a7cf2c69c5e988fb408712", + "sha1": "22391ec032d8cf2569c2c79daf9edd535fd5ae1f", "gitDir": "test/corpus/repos/javascript", - "sha2": "c8bd2718371b28040fa981ce35a138725b120aad" + "sha2": "d2e01036c8e33e37b082368f832c642e1498419d" } ,{ "testCaseDescription": "javascript-comment-replacement-test", @@ -152,8 +148,7 @@ } ] }, - "summary": "Replaced the '// This is a property' comment with the '/*\n * This is a method\n*/' comment", - "tag": "JSONSummary" + "summary": "Replaced the '// This is a property' comment with the '/*\n * This is a method\n*/' comment" } ] }, @@ -162,9 +157,9 @@ "filePaths": [ "comment.js" ], - "sha1": "c8bd2718371b28040fa981ce35a138725b120aad", + "sha1": "d2e01036c8e33e37b082368f832c642e1498419d", "gitDir": "test/corpus/repos/javascript", - "sha2": "f638e783e9d0ee750f8f201471d4b1b9e9f3f9a3" + "sha2": "53dd565d968e321c83e7d55a640b941ec039ae9d" } ,{ "testCaseDescription": "javascript-comment-delete-replacement-test", @@ -184,8 +179,7 @@ ] } }, - "summary": "Deleted the '/*\n * This is a method\n*/' comment", - "tag": "JSONSummary" + "summary": "Deleted the '/*\n * This is a method\n*/' comment" }, { "span": { @@ -200,8 +194,7 @@ ] } }, - "summary": "Deleted the '// This is a property' comment", - "tag": "JSONSummary" + "summary": "Deleted the '// This is a property' comment" }, { "span": { @@ -216,8 +209,7 @@ ] } }, - "summary": "Added the '/*\n * This is a method\n*/' comment", - "tag": "JSONSummary" + "summary": "Added the '/*\n * This is a method\n*/' comment" } ] }, @@ -226,9 +218,9 @@ "filePaths": [ "comment.js" ], - "sha1": "f638e783e9d0ee750f8f201471d4b1b9e9f3f9a3", + "sha1": "53dd565d968e321c83e7d55a640b941ec039ae9d", "gitDir": "test/corpus/repos/javascript", - "sha2": "48711051e73107b9a44cf4c146dbdbdcafea224f" + "sha2": "f44bdb127231af5416f02054c41452de18136eb1" } ,{ "testCaseDescription": "javascript-comment-delete-test", @@ -248,8 +240,7 @@ ] } }, - "summary": "Deleted the '// This is a property' comment", - "tag": "JSONSummary" + "summary": "Deleted the '// This is a property' comment" } ] }, @@ -258,9 +249,9 @@ "filePaths": [ "comment.js" ], - "sha1": "48711051e73107b9a44cf4c146dbdbdcafea224f", + "sha1": "f44bdb127231af5416f02054c41452de18136eb1", "gitDir": "test/corpus/repos/javascript", - "sha2": "8446a2ada4c302787a76d6f8654f66e0f14e9fa6" + "sha2": "4d5c2aa9348d27a4efe63e93dd6ea597d1ab60f0" } ,{ "testCaseDescription": "javascript-comment-delete-rest-test", @@ -280,8 +271,7 @@ ] } }, - "summary": "Deleted the '/*\n * This is a method\n*/' comment", - "tag": "JSONSummary" + "summary": "Deleted the '/*\n * This is a method\n*/' comment" } ] }, @@ -290,7 +280,7 @@ "filePaths": [ "comment.js" ], - "sha1": "8446a2ada4c302787a76d6f8654f66e0f14e9fa6", + "sha1": "4d5c2aa9348d27a4efe63e93dd6ea597d1ab60f0", "gitDir": "test/corpus/repos/javascript", - "sha2": "af31bc75c5b7a9054f10c295c885d0cc2c5d1d06" + "sha2": "d0223efd366c0d9b703a6edf4b9961fa26add3cb" }] diff --git a/test/corpus/diff-summaries/javascript/constructor-call.json b/test/corpus/diff-summaries/javascript/constructor-call.json index 52a26271f..abe952ed7 100644 --- a/test/corpus/diff-summaries/javascript/constructor-call.json +++ b/test/corpus/diff-summaries/javascript/constructor-call.json @@ -16,8 +16,7 @@ ] } }, - "summary": "Added the 'module.Klass(1, \"two\")' constructor", - "tag": "JSONSummary" + "summary": "Added the 'module.Klass(1, \"two\")' constructor" } ] }, @@ -26,9 +25,9 @@ "filePaths": [ "constructor-call.js" ], - "sha1": "37b9064285baa63e16cc6b1c4b5128fed52fa082", + "sha1": "d338b275731ec3d9b527339e1ac1b99f43ea5ea2", "gitDir": "test/corpus/repos/javascript", - "sha2": "b8f33f052773b435e5d29e89aeaf9cf8b3a9e8a6" + "sha2": "07f0e420ba82a7a88edead9753bf001dc427c900" } ,{ "testCaseDescription": "javascript-constructor-call-replacement-insert-test", @@ -48,8 +47,7 @@ ] } }, - "summary": "Added the 'module.Klass(1, \"three\")' constructor", - "tag": "JSONSummary" + "summary": "Added the 'module.Klass(1, \"three\")' constructor" }, { "span": { @@ -64,8 +62,7 @@ ] } }, - "summary": "Added the 'module.Klass(1, \"two\")' constructor", - "tag": "JSONSummary" + "summary": "Added the 'module.Klass(1, \"two\")' constructor" } ] }, @@ -74,9 +71,9 @@ "filePaths": [ "constructor-call.js" ], - "sha1": "b8f33f052773b435e5d29e89aeaf9cf8b3a9e8a6", + "sha1": "07f0e420ba82a7a88edead9753bf001dc427c900", "gitDir": "test/corpus/repos/javascript", - "sha2": "fa501924dbaed310d84435b0c33ef97a068653e4" + "sha2": "0ead57e4c68d3441874607df82f10cfae180871c" } ,{ "testCaseDescription": "javascript-constructor-call-delete-insert-test", @@ -108,8 +105,7 @@ } ] }, - "summary": "Replaced the \"three\" string with the \"two\" string in the module.Klass(1, \"two\") method call", - "tag": "JSONSummary" + "summary": "Replaced the \"three\" string with the \"two\" string in the module.Klass(1, \"two\") method call" } ] }, @@ -118,9 +114,9 @@ "filePaths": [ "constructor-call.js" ], - "sha1": "fa501924dbaed310d84435b0c33ef97a068653e4", + "sha1": "0ead57e4c68d3441874607df82f10cfae180871c", "gitDir": "test/corpus/repos/javascript", - "sha2": "9c7fb90945f08ad72efbcd243221cef5ce8d9732" + "sha2": "5312cfad6882b93031aaa4aa6bf94db1cb6097a1" } ,{ "testCaseDescription": "javascript-constructor-call-replacement-test", @@ -152,8 +148,7 @@ } ] }, - "summary": "Replaced the \"two\" string with the \"three\" string in the module.Klass(1, \"three\") method call", - "tag": "JSONSummary" + "summary": "Replaced the \"two\" string with the \"three\" string in the module.Klass(1, \"three\") method call" } ] }, @@ -162,9 +157,9 @@ "filePaths": [ "constructor-call.js" ], - "sha1": "9c7fb90945f08ad72efbcd243221cef5ce8d9732", + "sha1": "5312cfad6882b93031aaa4aa6bf94db1cb6097a1", "gitDir": "test/corpus/repos/javascript", - "sha2": "bb66b026044f3944a08fec17c572b7b8867decda" + "sha2": "d1ce2f7e01d8a6fb58e25e00612be76b5a92129b" } ,{ "testCaseDescription": "javascript-constructor-call-delete-replacement-test", @@ -184,8 +179,7 @@ ] } }, - "summary": "Deleted the 'module.Klass(1, \"three\")' constructor", - "tag": "JSONSummary" + "summary": "Deleted the 'module.Klass(1, \"three\")' constructor" }, { "span": { @@ -200,8 +194,7 @@ ] } }, - "summary": "Deleted the 'module.Klass(1, \"two\")' constructor", - "tag": "JSONSummary" + "summary": "Deleted the 'module.Klass(1, \"two\")' constructor" }, { "span": { @@ -216,8 +209,7 @@ ] } }, - "summary": "Added the 'module.Klass(1, \"three\")' constructor", - "tag": "JSONSummary" + "summary": "Added the 'module.Klass(1, \"three\")' constructor" } ] }, @@ -226,9 +218,9 @@ "filePaths": [ "constructor-call.js" ], - "sha1": "bb66b026044f3944a08fec17c572b7b8867decda", + "sha1": "d1ce2f7e01d8a6fb58e25e00612be76b5a92129b", "gitDir": "test/corpus/repos/javascript", - "sha2": "3669aebc1d501fba80efddd2a0b53b669b045ffa" + "sha2": "f2947ecde2c4966ba63934c2bf9fadb1bf9494a5" } ,{ "testCaseDescription": "javascript-constructor-call-delete-test", @@ -248,8 +240,7 @@ ] } }, - "summary": "Deleted the 'module.Klass(1, \"two\")' constructor", - "tag": "JSONSummary" + "summary": "Deleted the 'module.Klass(1, \"two\")' constructor" } ] }, @@ -258,9 +249,9 @@ "filePaths": [ "constructor-call.js" ], - "sha1": "3669aebc1d501fba80efddd2a0b53b669b045ffa", + "sha1": "f2947ecde2c4966ba63934c2bf9fadb1bf9494a5", "gitDir": "test/corpus/repos/javascript", - "sha2": "aada0c4456c077928d7b286809c61323c9315147" + "sha2": "3f2450813b57ef20f48fafa20ec30d660a296e5c" } ,{ "testCaseDescription": "javascript-constructor-call-delete-rest-test", @@ -280,8 +271,7 @@ ] } }, - "summary": "Deleted the 'module.Klass(1, \"three\")' constructor", - "tag": "JSONSummary" + "summary": "Deleted the 'module.Klass(1, \"three\")' constructor" } ] }, @@ -290,7 +280,7 @@ "filePaths": [ "constructor-call.js" ], - "sha1": "aada0c4456c077928d7b286809c61323c9315147", + "sha1": "3f2450813b57ef20f48fafa20ec30d660a296e5c", "gitDir": "test/corpus/repos/javascript", - "sha2": "770dfcd929f8deaec3cf8028327930c422ee1814" + "sha2": "d6f65326cb55e5d2b83057d59ae062b3f4bc778e" }] diff --git a/test/corpus/diff-summaries/javascript/delete-operator.json b/test/corpus/diff-summaries/javascript/delete-operator.json index 7a7a9578b..cb7a6b757 100644 --- a/test/corpus/diff-summaries/javascript/delete-operator.json +++ b/test/corpus/diff-summaries/javascript/delete-operator.json @@ -16,8 +16,7 @@ ] } }, - "summary": "Added the 'delete thing['prop']' operator", - "tag": "JSONSummary" + "summary": "Added the 'delete thing['prop']' operator" } ] }, @@ -26,9 +25,9 @@ "filePaths": [ "delete-operator.js" ], - "sha1": "34d611dc6839b42bba50f800508e3c1eed940690", + "sha1": "660d4f31a366c484dcf287cc129d2236e0064639", "gitDir": "test/corpus/repos/javascript", - "sha2": "9c01dfb007ff3853c71c2ed944ccf83ae4a4899e" + "sha2": "dcdf4363cc41756d111762831febfeb2bc5c3561" } ,{ "testCaseDescription": "javascript-delete-operator-replacement-insert-test", @@ -48,8 +47,7 @@ ] } }, - "summary": "Added the 'delete thing.prop' operator", - "tag": "JSONSummary" + "summary": "Added the 'delete thing.prop' operator" }, { "span": { @@ -64,8 +62,7 @@ ] } }, - "summary": "Added the 'delete thing['prop']' operator", - "tag": "JSONSummary" + "summary": "Added the 'delete thing['prop']' operator" } ] }, @@ -74,9 +71,9 @@ "filePaths": [ "delete-operator.js" ], - "sha1": "9c01dfb007ff3853c71c2ed944ccf83ae4a4899e", + "sha1": "dcdf4363cc41756d111762831febfeb2bc5c3561", "gitDir": "test/corpus/repos/javascript", - "sha2": "fcd04c63372795e232f0ab1dc003078a11e23348" + "sha2": "b9195fb8317d07798a424a3ad5897669cf2fec4d" } ,{ "testCaseDescription": "javascript-delete-operator-delete-insert-test", @@ -108,8 +105,7 @@ } ] }, - "summary": "Replaced the 'delete thing.prop' operator with the 'delete thing['prop']' operator", - "tag": "JSONSummary" + "summary": "Replaced the 'delete thing.prop' operator with the 'delete thing['prop']' operator" } ] }, @@ -118,9 +114,9 @@ "filePaths": [ "delete-operator.js" ], - "sha1": "fcd04c63372795e232f0ab1dc003078a11e23348", + "sha1": "b9195fb8317d07798a424a3ad5897669cf2fec4d", "gitDir": "test/corpus/repos/javascript", - "sha2": "54acda735d0aa3817a65ab8bae18ac9c3249299f" + "sha2": "b1aa406089e4aafef90ec5732ba443d1031f561e" } ,{ "testCaseDescription": "javascript-delete-operator-replacement-test", @@ -152,8 +148,7 @@ } ] }, - "summary": "Replaced the 'delete thing['prop']' operator with the 'delete thing.prop' operator", - "tag": "JSONSummary" + "summary": "Replaced the 'delete thing['prop']' operator with the 'delete thing.prop' operator" } ] }, @@ -162,9 +157,9 @@ "filePaths": [ "delete-operator.js" ], - "sha1": "54acda735d0aa3817a65ab8bae18ac9c3249299f", + "sha1": "b1aa406089e4aafef90ec5732ba443d1031f561e", "gitDir": "test/corpus/repos/javascript", - "sha2": "16e956f11b3ecc44abf81b4c33cddbd36c9222a7" + "sha2": "3d47f770de2c100cdd3f5cfcb8bc43f582e4a368" } ,{ "testCaseDescription": "javascript-delete-operator-delete-replacement-test", @@ -184,8 +179,7 @@ ] } }, - "summary": "Deleted the 'delete thing.prop' operator", - "tag": "JSONSummary" + "summary": "Deleted the 'delete thing.prop' operator" }, { "span": { @@ -200,8 +194,7 @@ ] } }, - "summary": "Deleted the 'delete thing['prop']' operator", - "tag": "JSONSummary" + "summary": "Deleted the 'delete thing['prop']' operator" }, { "span": { @@ -216,8 +209,7 @@ ] } }, - "summary": "Added the 'delete thing.prop' operator", - "tag": "JSONSummary" + "summary": "Added the 'delete thing.prop' operator" } ] }, @@ -226,9 +218,9 @@ "filePaths": [ "delete-operator.js" ], - "sha1": "16e956f11b3ecc44abf81b4c33cddbd36c9222a7", + "sha1": "3d47f770de2c100cdd3f5cfcb8bc43f582e4a368", "gitDir": "test/corpus/repos/javascript", - "sha2": "91fc755fdc45f6c82da10cdb9078ff2d8ec66c9c" + "sha2": "79ed3766548499729284c8eb3ff3cecfaed80a4c" } ,{ "testCaseDescription": "javascript-delete-operator-delete-test", @@ -248,8 +240,7 @@ ] } }, - "summary": "Deleted the 'delete thing['prop']' operator", - "tag": "JSONSummary" + "summary": "Deleted the 'delete thing['prop']' operator" } ] }, @@ -258,9 +249,9 @@ "filePaths": [ "delete-operator.js" ], - "sha1": "91fc755fdc45f6c82da10cdb9078ff2d8ec66c9c", + "sha1": "79ed3766548499729284c8eb3ff3cecfaed80a4c", "gitDir": "test/corpus/repos/javascript", - "sha2": "dadef7d3a1d78afcdb53140c1c32f0bd93f75580" + "sha2": "3b8b6b7c801a89beb229c8f9b705be4d4465b622" } ,{ "testCaseDescription": "javascript-delete-operator-delete-rest-test", @@ -280,8 +271,7 @@ ] } }, - "summary": "Deleted the 'delete thing.prop' operator", - "tag": "JSONSummary" + "summary": "Deleted the 'delete thing.prop' operator" } ] }, @@ -290,7 +280,7 @@ "filePaths": [ "delete-operator.js" ], - "sha1": "dadef7d3a1d78afcdb53140c1c32f0bd93f75580", + "sha1": "3b8b6b7c801a89beb229c8f9b705be4d4465b622", "gitDir": "test/corpus/repos/javascript", - "sha2": "d14d7b09c6761ab1a14c5aeda0a105d44c520617" + "sha2": "8f71c3ee15ecf75d5d1aa9d7f9e82346c26b78e1" }] diff --git a/test/corpus/diff-summaries/javascript/do-while-statement.json b/test/corpus/diff-summaries/javascript/do-while-statement.json index 3eedde9ba..6b1906a61 100644 --- a/test/corpus/diff-summaries/javascript/do-while-statement.json +++ b/test/corpus/diff-summaries/javascript/do-while-statement.json @@ -16,8 +16,7 @@ ] } }, - "summary": "Added the 'true' do/while statement", - "tag": "JSONSummary" + "summary": "Added the 'true' do/while statement" } ] }, @@ -26,9 +25,9 @@ "filePaths": [ "do-while-statement.js" ], - "sha1": "3dadf24ea6dd60cf63f2599d16951764a34aea81", + "sha1": "c5a33a05e7c473051b69c27b5268f7e73d9f9818", "gitDir": "test/corpus/repos/javascript", - "sha2": "5ac1a1a4fe9eda5e5fd161253a6d91501f1b3ce1" + "sha2": "f6d13c24db646eabb87a5569fab5dc059397cd41" } ,{ "testCaseDescription": "javascript-do-while-statement-replacement-insert-test", @@ -48,8 +47,7 @@ ] } }, - "summary": "Added the 'false' do/while statement", - "tag": "JSONSummary" + "summary": "Added the 'false' do/while statement" }, { "span": { @@ -64,8 +62,7 @@ ] } }, - "summary": "Added the 'true' do/while statement", - "tag": "JSONSummary" + "summary": "Added the 'true' do/while statement" } ] }, @@ -74,9 +71,9 @@ "filePaths": [ "do-while-statement.js" ], - "sha1": "5ac1a1a4fe9eda5e5fd161253a6d91501f1b3ce1", + "sha1": "f6d13c24db646eabb87a5569fab5dc059397cd41", "gitDir": "test/corpus/repos/javascript", - "sha2": "ba86b912e5954ec48b6e49bca4c6bf3f24debf71" + "sha2": "b97e52feb5f9b94c2f7c035a5c0b741ab2709c11" } ,{ "testCaseDescription": "javascript-do-while-statement-delete-insert-test", @@ -108,8 +105,7 @@ } ] }, - "summary": "Replaced the 'replacement' identifier with the 'insert' identifier in the console.log(insert) method call", - "tag": "JSONSummary" + "summary": "Replaced the 'replacement' identifier with the 'insert' identifier in the console.log(insert) method call" }, { "span": { @@ -136,8 +132,7 @@ } ] }, - "summary": "Replaced 'false' with 'true' in the true do/while statement", - "tag": "JSONSummary" + "summary": "Replaced 'false' with 'true' in the true do/while statement" } ] }, @@ -146,9 +141,9 @@ "filePaths": [ "do-while-statement.js" ], - "sha1": "ba86b912e5954ec48b6e49bca4c6bf3f24debf71", + "sha1": "b97e52feb5f9b94c2f7c035a5c0b741ab2709c11", "gitDir": "test/corpus/repos/javascript", - "sha2": "224a8c099bc7a1282813dd3f2d4ed7d8c87a3f0f" + "sha2": "618521ec11773660442d22c09e5616569ee0d4d6" } ,{ "testCaseDescription": "javascript-do-while-statement-replacement-test", @@ -180,8 +175,7 @@ } ] }, - "summary": "Replaced the 'insert' identifier with the 'replacement' identifier in the console.log(replacement) method call", - "tag": "JSONSummary" + "summary": "Replaced the 'insert' identifier with the 'replacement' identifier in the console.log(replacement) method call" }, { "span": { @@ -208,8 +202,7 @@ } ] }, - "summary": "Replaced 'true' with 'false' in the false do/while statement", - "tag": "JSONSummary" + "summary": "Replaced 'true' with 'false' in the false do/while statement" } ] }, @@ -218,9 +211,9 @@ "filePaths": [ "do-while-statement.js" ], - "sha1": "224a8c099bc7a1282813dd3f2d4ed7d8c87a3f0f", + "sha1": "618521ec11773660442d22c09e5616569ee0d4d6", "gitDir": "test/corpus/repos/javascript", - "sha2": "1363c42479d68b43b946500050acea6a3ec19511" + "sha2": "b058c2ef89ec07779649681bb0867d7ca642a924" } ,{ "testCaseDescription": "javascript-do-while-statement-delete-replacement-test", @@ -240,8 +233,7 @@ ] } }, - "summary": "Deleted the 'false' do/while statement", - "tag": "JSONSummary" + "summary": "Deleted the 'false' do/while statement" }, { "span": { @@ -256,8 +248,7 @@ ] } }, - "summary": "Deleted the 'true' do/while statement", - "tag": "JSONSummary" + "summary": "Deleted the 'true' do/while statement" }, { "span": { @@ -272,8 +263,7 @@ ] } }, - "summary": "Added the 'false' do/while statement", - "tag": "JSONSummary" + "summary": "Added the 'false' do/while statement" } ] }, @@ -282,9 +272,9 @@ "filePaths": [ "do-while-statement.js" ], - "sha1": "1363c42479d68b43b946500050acea6a3ec19511", + "sha1": "b058c2ef89ec07779649681bb0867d7ca642a924", "gitDir": "test/corpus/repos/javascript", - "sha2": "feb5169e88f28961b09f7527b8af6819931f39f3" + "sha2": "29a60219132b7497d5f2f2da75cd6fad3583ea3e" } ,{ "testCaseDescription": "javascript-do-while-statement-delete-test", @@ -304,8 +294,7 @@ ] } }, - "summary": "Deleted the 'true' do/while statement", - "tag": "JSONSummary" + "summary": "Deleted the 'true' do/while statement" } ] }, @@ -314,9 +303,9 @@ "filePaths": [ "do-while-statement.js" ], - "sha1": "feb5169e88f28961b09f7527b8af6819931f39f3", + "sha1": "29a60219132b7497d5f2f2da75cd6fad3583ea3e", "gitDir": "test/corpus/repos/javascript", - "sha2": "e6b31e8c000b83aef153563e940ba6753a81aa13" + "sha2": "2c0695fb799f92e9549bea04968f0a7db55e5084" } ,{ "testCaseDescription": "javascript-do-while-statement-delete-rest-test", @@ -336,8 +325,7 @@ ] } }, - "summary": "Deleted the 'false' do/while statement", - "tag": "JSONSummary" + "summary": "Deleted the 'false' do/while statement" } ] }, @@ -346,7 +334,7 @@ "filePaths": [ "do-while-statement.js" ], - "sha1": "e6b31e8c000b83aef153563e940ba6753a81aa13", + "sha1": "2c0695fb799f92e9549bea04968f0a7db55e5084", "gitDir": "test/corpus/repos/javascript", - "sha2": "a61175fe3edb3376731a61e36fbe795857288cb2" + "sha2": "64789b8e632a3b70997ef3abb4ce031bb19cbedb" }] diff --git a/test/corpus/diff-summaries/javascript/false.json b/test/corpus/diff-summaries/javascript/false.json index 0df5d715e..6798a209c 100644 --- a/test/corpus/diff-summaries/javascript/false.json +++ b/test/corpus/diff-summaries/javascript/false.json @@ -16,8 +16,7 @@ ] } }, - "summary": "Added 'false'", - "tag": "JSONSummary" + "summary": "Added 'false'" } ] }, @@ -26,9 +25,9 @@ "filePaths": [ "false.js" ], - "sha1": "bc59c08d8b5b00715bbf8e852bee86bfed8d5f03", + "sha1": "6f781fd1c75a5c824323b66e61fb2717755b4753", "gitDir": "test/corpus/repos/javascript", - "sha2": "0e8162ddf892bf944707eefa68da4d8c3097ee5e" + "sha2": "4973cc5fa83113e784f59efc0e9e2bee97ac8a4d" } ,{ "testCaseDescription": "javascript-false-replacement-insert-test", @@ -48,8 +47,7 @@ ] } }, - "summary": "Added the 'false' return statement", - "tag": "JSONSummary" + "summary": "Added the 'false' return statement" }, { "span": { @@ -64,8 +62,7 @@ ] } }, - "summary": "Added 'false'", - "tag": "JSONSummary" + "summary": "Added 'false'" } ] }, @@ -74,9 +71,9 @@ "filePaths": [ "false.js" ], - "sha1": "0e8162ddf892bf944707eefa68da4d8c3097ee5e", + "sha1": "4973cc5fa83113e784f59efc0e9e2bee97ac8a4d", "gitDir": "test/corpus/repos/javascript", - "sha2": "827e84992521a53a4672e7487814a3d904570c3c" + "sha2": "6bd0e7e033d1921b69c9740f08c5575c7e5e6ee1" } ,{ "testCaseDescription": "javascript-false-delete-insert-test", @@ -96,8 +93,7 @@ ] } }, - "summary": "Added 'false'", - "tag": "JSONSummary" + "summary": "Added 'false'" }, { "span": { @@ -112,8 +108,7 @@ ] } }, - "summary": "Deleted the 'false' return statement", - "tag": "JSONSummary" + "summary": "Deleted the 'false' return statement" } ] }, @@ -122,9 +117,9 @@ "filePaths": [ "false.js" ], - "sha1": "827e84992521a53a4672e7487814a3d904570c3c", + "sha1": "6bd0e7e033d1921b69c9740f08c5575c7e5e6ee1", "gitDir": "test/corpus/repos/javascript", - "sha2": "8ad16f2c510212119c87a32df1d0661c7f091533" + "sha2": "b2db9c4bb0b3a8d6b68d683e8513b2f6efedb44b" } ,{ "testCaseDescription": "javascript-false-replacement-test", @@ -144,8 +139,7 @@ ] } }, - "summary": "Added the 'false' return statement", - "tag": "JSONSummary" + "summary": "Added the 'false' return statement" }, { "span": { @@ -160,8 +154,7 @@ ] } }, - "summary": "Deleted 'false'", - "tag": "JSONSummary" + "summary": "Deleted 'false'" } ] }, @@ -170,9 +163,9 @@ "filePaths": [ "false.js" ], - "sha1": "8ad16f2c510212119c87a32df1d0661c7f091533", + "sha1": "b2db9c4bb0b3a8d6b68d683e8513b2f6efedb44b", "gitDir": "test/corpus/repos/javascript", - "sha2": "5665bce4ee27c2b5f56afbc88b0ca17f85902c6a" + "sha2": "dd9ec604931ffffba1b6c7bd4773ec8ac5418804" } ,{ "testCaseDescription": "javascript-false-delete-replacement-test", @@ -192,8 +185,7 @@ ] } }, - "summary": "Deleted the 'false' return statement", - "tag": "JSONSummary" + "summary": "Deleted the 'false' return statement" }, { "span": { @@ -208,8 +200,7 @@ ] } }, - "summary": "Deleted 'false'", - "tag": "JSONSummary" + "summary": "Deleted 'false'" }, { "span": { @@ -224,8 +215,7 @@ ] } }, - "summary": "Added the 'false' return statement", - "tag": "JSONSummary" + "summary": "Added the 'false' return statement" } ] }, @@ -234,9 +224,9 @@ "filePaths": [ "false.js" ], - "sha1": "5665bce4ee27c2b5f56afbc88b0ca17f85902c6a", + "sha1": "dd9ec604931ffffba1b6c7bd4773ec8ac5418804", "gitDir": "test/corpus/repos/javascript", - "sha2": "5e7609a2a963055a420461b6743e96adb7cf9b88" + "sha2": "4b8dddf41a7b9ac76de8ff5eb1327fb0bd1f8dcb" } ,{ "testCaseDescription": "javascript-false-delete-test", @@ -256,8 +246,7 @@ ] } }, - "summary": "Deleted 'false'", - "tag": "JSONSummary" + "summary": "Deleted 'false'" } ] }, @@ -266,9 +255,9 @@ "filePaths": [ "false.js" ], - "sha1": "5e7609a2a963055a420461b6743e96adb7cf9b88", + "sha1": "4b8dddf41a7b9ac76de8ff5eb1327fb0bd1f8dcb", "gitDir": "test/corpus/repos/javascript", - "sha2": "1a3f66f5555eef7dbe41dd82451d089a5c3648d6" + "sha2": "2f2527a35cc4511ba3e91e4360f61e56f20d9c3e" } ,{ "testCaseDescription": "javascript-false-delete-rest-test", @@ -288,8 +277,7 @@ ] } }, - "summary": "Deleted the 'false' return statement", - "tag": "JSONSummary" + "summary": "Deleted the 'false' return statement" } ] }, @@ -298,7 +286,7 @@ "filePaths": [ "false.js" ], - "sha1": "1a3f66f5555eef7dbe41dd82451d089a5c3648d6", + "sha1": "2f2527a35cc4511ba3e91e4360f61e56f20d9c3e", "gitDir": "test/corpus/repos/javascript", - "sha2": "87ef7d96585dfee34d9371968cd3cbec7f8a1d97" + "sha2": "7f7c1c904ffcc4ea539925a1d336147d84fd90b8" }] diff --git a/test/corpus/diff-summaries/javascript/for-in-statement.json b/test/corpus/diff-summaries/javascript/for-in-statement.json index fcec7698b..c25af1144 100644 --- a/test/corpus/diff-summaries/javascript/for-in-statement.json +++ b/test/corpus/diff-summaries/javascript/for-in-statement.json @@ -16,8 +16,7 @@ ] } }, - "summary": "Added the 'thing in things' for statement", - "tag": "JSONSummary" + "summary": "Added the 'thing in things' for statement" } ] }, @@ -26,9 +25,9 @@ "filePaths": [ "for-in-statement.js" ], - "sha1": "12a3949b01e7ecc688735f731b84ba631a80c1c1", + "sha1": "1e9729897fa1da1617386fa8da290df973dadc93", "gitDir": "test/corpus/repos/javascript", - "sha2": "568db4c6d69437c83ad4d9eece85fb2d40203527" + "sha2": "e5d8b7d6f07410e2fa00bbec5718bbdf061166fa" } ,{ "testCaseDescription": "javascript-for-in-statement-replacement-insert-test", @@ -48,8 +47,7 @@ ] } }, - "summary": "Added the 'item in items' for statement", - "tag": "JSONSummary" + "summary": "Added the 'item in items' for statement" }, { "span": { @@ -64,8 +62,7 @@ ] } }, - "summary": "Added the 'thing in things' for statement", - "tag": "JSONSummary" + "summary": "Added the 'thing in things' for statement" } ] }, @@ -74,9 +71,9 @@ "filePaths": [ "for-in-statement.js" ], - "sha1": "568db4c6d69437c83ad4d9eece85fb2d40203527", + "sha1": "e5d8b7d6f07410e2fa00bbec5718bbdf061166fa", "gitDir": "test/corpus/repos/javascript", - "sha2": "424256ee4d0b8003e66b38b569c8a5200616560e" + "sha2": "6c8ba52447c2faf8fed1eba65cd64c643003461f" } ,{ "testCaseDescription": "javascript-for-in-statement-delete-insert-test", @@ -108,8 +105,7 @@ } ] }, - "summary": "Replaced the 'item' identifier with the 'thing' identifier", - "tag": "JSONSummary" + "summary": "Replaced the 'item' identifier with the 'thing' identifier" }, { "span": { @@ -136,8 +132,7 @@ } ] }, - "summary": "Replaced the 'items' identifier with the 'things' identifier", - "tag": "JSONSummary" + "summary": "Replaced the 'items' identifier with the 'things' identifier" }, { "span": { @@ -164,8 +159,7 @@ } ] }, - "summary": "Replaced the 'item' identifier with the 'thing' identifier in the thing() function call", - "tag": "JSONSummary" + "summary": "Replaced the 'item' identifier with the 'thing' identifier in the thing() function call" } ] }, @@ -174,9 +168,9 @@ "filePaths": [ "for-in-statement.js" ], - "sha1": "424256ee4d0b8003e66b38b569c8a5200616560e", + "sha1": "6c8ba52447c2faf8fed1eba65cd64c643003461f", "gitDir": "test/corpus/repos/javascript", - "sha2": "e57446ddf477ccf71ad7f59e4a935f2fb09bdad9" + "sha2": "bc392f77e718987c79b53126053665c245b163ac" } ,{ "testCaseDescription": "javascript-for-in-statement-replacement-test", @@ -208,8 +202,7 @@ } ] }, - "summary": "Replaced the 'thing' identifier with the 'item' identifier", - "tag": "JSONSummary" + "summary": "Replaced the 'thing' identifier with the 'item' identifier" }, { "span": { @@ -236,8 +229,7 @@ } ] }, - "summary": "Replaced the 'things' identifier with the 'items' identifier", - "tag": "JSONSummary" + "summary": "Replaced the 'things' identifier with the 'items' identifier" }, { "span": { @@ -264,8 +256,7 @@ } ] }, - "summary": "Replaced the 'thing' identifier with the 'item' identifier in the item() function call", - "tag": "JSONSummary" + "summary": "Replaced the 'thing' identifier with the 'item' identifier in the item() function call" } ] }, @@ -274,9 +265,9 @@ "filePaths": [ "for-in-statement.js" ], - "sha1": "e57446ddf477ccf71ad7f59e4a935f2fb09bdad9", + "sha1": "bc392f77e718987c79b53126053665c245b163ac", "gitDir": "test/corpus/repos/javascript", - "sha2": "e652cb33755d7d6c916910cdec530b0608efc157" + "sha2": "da2eb693e4cc262362cb81c3fdd040af92eecc42" } ,{ "testCaseDescription": "javascript-for-in-statement-delete-replacement-test", @@ -296,8 +287,7 @@ ] } }, - "summary": "Deleted the 'item in items' for statement", - "tag": "JSONSummary" + "summary": "Deleted the 'item in items' for statement" }, { "span": { @@ -312,8 +302,7 @@ ] } }, - "summary": "Deleted the 'thing in things' for statement", - "tag": "JSONSummary" + "summary": "Deleted the 'thing in things' for statement" }, { "span": { @@ -328,8 +317,7 @@ ] } }, - "summary": "Added the 'item in items' for statement", - "tag": "JSONSummary" + "summary": "Added the 'item in items' for statement" } ] }, @@ -338,9 +326,9 @@ "filePaths": [ "for-in-statement.js" ], - "sha1": "e652cb33755d7d6c916910cdec530b0608efc157", + "sha1": "da2eb693e4cc262362cb81c3fdd040af92eecc42", "gitDir": "test/corpus/repos/javascript", - "sha2": "f7bdd90fd30fb31f8b8c9e2c2ccfd43f327cb9cf" + "sha2": "210a8ed2aa30b91ca470694492daa7412c616d58" } ,{ "testCaseDescription": "javascript-for-in-statement-delete-test", @@ -360,8 +348,7 @@ ] } }, - "summary": "Deleted the 'thing in things' for statement", - "tag": "JSONSummary" + "summary": "Deleted the 'thing in things' for statement" } ] }, @@ -370,9 +357,9 @@ "filePaths": [ "for-in-statement.js" ], - "sha1": "f7bdd90fd30fb31f8b8c9e2c2ccfd43f327cb9cf", + "sha1": "210a8ed2aa30b91ca470694492daa7412c616d58", "gitDir": "test/corpus/repos/javascript", - "sha2": "2f59732701f26c61644d9cfde92375851a7d6ec4" + "sha2": "89852450722771842d4365c760a1403957fc7c96" } ,{ "testCaseDescription": "javascript-for-in-statement-delete-rest-test", @@ -392,8 +379,7 @@ ] } }, - "summary": "Deleted the 'item in items' for statement", - "tag": "JSONSummary" + "summary": "Deleted the 'item in items' for statement" } ] }, @@ -402,7 +388,7 @@ "filePaths": [ "for-in-statement.js" ], - "sha1": "2f59732701f26c61644d9cfde92375851a7d6ec4", + "sha1": "89852450722771842d4365c760a1403957fc7c96", "gitDir": "test/corpus/repos/javascript", - "sha2": "92dce519bc0a25951a62cfcf3a1069969a20938c" + "sha2": "e572fcdd9abd2fa13fdff57a3afd8b3c43a6c6a0" }] diff --git a/test/corpus/diff-summaries/javascript/for-loop-with-in-statement.json b/test/corpus/diff-summaries/javascript/for-loop-with-in-statement.json index 7d26d3efc..1b5a5527c 100644 --- a/test/corpus/diff-summaries/javascript/for-loop-with-in-statement.json +++ b/test/corpus/diff-summaries/javascript/for-loop-with-in-statement.json @@ -16,8 +16,7 @@ ] } }, - "summary": "Added the 'key in something && i = 0; i < n; i++' for statement", - "tag": "JSONSummary" + "summary": "Added the 'key in something && i = 0; i < n; i++' for statement" } ] }, @@ -26,9 +25,9 @@ "filePaths": [ "for-loop-with-in-statement.js" ], - "sha1": "2762aadfb1df20b18044fd4529c8cd573d357cc9", + "sha1": "954a81d340fc574299386d998fb6cd667fe875ce", "gitDir": "test/corpus/repos/javascript", - "sha2": "adad02fe14bb8fefc9437fed0725b7b49b837d04" + "sha2": "8e7957d2f5b2ec1db4345678a2abc67205202d7f" } ,{ "testCaseDescription": "javascript-for-loop-with-in-statement-replacement-insert-test", @@ -48,8 +47,7 @@ ] } }, - "summary": "Added the 'otherKey in something && i = 0; i < n; i++' for statement", - "tag": "JSONSummary" + "summary": "Added the 'otherKey in something && i = 0; i < n; i++' for statement" }, { "span": { @@ -64,8 +62,7 @@ ] } }, - "summary": "Added the 'key in something && i = 0; i < n; i++' for statement", - "tag": "JSONSummary" + "summary": "Added the 'key in something && i = 0; i < n; i++' for statement" } ] }, @@ -74,9 +71,9 @@ "filePaths": [ "for-loop-with-in-statement.js" ], - "sha1": "adad02fe14bb8fefc9437fed0725b7b49b837d04", + "sha1": "8e7957d2f5b2ec1db4345678a2abc67205202d7f", "gitDir": "test/corpus/repos/javascript", - "sha2": "1f3fc5b85a5281e578b3304181604b65217349e9" + "sha2": "8aafa0ba7361d24eecc7b67f364b96fb0e1783d9" } ,{ "testCaseDescription": "javascript-for-loop-with-in-statement-delete-insert-test", @@ -108,8 +105,7 @@ } ] }, - "summary": "Replaced the 'otherKey' identifier with the 'key' identifier", - "tag": "JSONSummary" + "summary": "Replaced the 'otherKey' identifier with the 'key' identifier" }, { "span": { @@ -136,8 +132,7 @@ } ] }, - "summary": "Replaced the 'doOtherSomething' identifier with the 'doSomething' identifier in the doSomething() function call", - "tag": "JSONSummary" + "summary": "Replaced the 'doOtherSomething' identifier with the 'doSomething' identifier in the doSomething() function call" } ] }, @@ -146,9 +141,9 @@ "filePaths": [ "for-loop-with-in-statement.js" ], - "sha1": "1f3fc5b85a5281e578b3304181604b65217349e9", + "sha1": "8aafa0ba7361d24eecc7b67f364b96fb0e1783d9", "gitDir": "test/corpus/repos/javascript", - "sha2": "14938b92d64697c66364baabc4277e0cd925f9d9" + "sha2": "ba14e6d7fb2d573306e97d6440a31bfd4ba358f7" } ,{ "testCaseDescription": "javascript-for-loop-with-in-statement-replacement-test", @@ -180,8 +175,7 @@ } ] }, - "summary": "Replaced the 'key' identifier with the 'otherKey' identifier", - "tag": "JSONSummary" + "summary": "Replaced the 'key' identifier with the 'otherKey' identifier" }, { "span": { @@ -208,8 +202,7 @@ } ] }, - "summary": "Replaced the 'doSomething' identifier with the 'doOtherSomething' identifier in the doOtherSomething() function call", - "tag": "JSONSummary" + "summary": "Replaced the 'doSomething' identifier with the 'doOtherSomething' identifier in the doOtherSomething() function call" } ] }, @@ -218,9 +211,9 @@ "filePaths": [ "for-loop-with-in-statement.js" ], - "sha1": "14938b92d64697c66364baabc4277e0cd925f9d9", + "sha1": "ba14e6d7fb2d573306e97d6440a31bfd4ba358f7", "gitDir": "test/corpus/repos/javascript", - "sha2": "44b34c087ea7c44395cd8fc72818925eeb24b67e" + "sha2": "99930dbd3a9f28d37aeda9c4746c210df0912e72" } ,{ "testCaseDescription": "javascript-for-loop-with-in-statement-delete-replacement-test", @@ -240,8 +233,7 @@ ] } }, - "summary": "Deleted the 'otherKey in something && i = 0; i < n; i++' for statement", - "tag": "JSONSummary" + "summary": "Deleted the 'otherKey in something && i = 0; i < n; i++' for statement" }, { "span": { @@ -256,8 +248,7 @@ ] } }, - "summary": "Deleted the 'key in something && i = 0; i < n; i++' for statement", - "tag": "JSONSummary" + "summary": "Deleted the 'key in something && i = 0; i < n; i++' for statement" }, { "span": { @@ -272,8 +263,7 @@ ] } }, - "summary": "Added the 'otherKey in something && i = 0; i < n; i++' for statement", - "tag": "JSONSummary" + "summary": "Added the 'otherKey in something && i = 0; i < n; i++' for statement" } ] }, @@ -282,9 +272,9 @@ "filePaths": [ "for-loop-with-in-statement.js" ], - "sha1": "44b34c087ea7c44395cd8fc72818925eeb24b67e", + "sha1": "99930dbd3a9f28d37aeda9c4746c210df0912e72", "gitDir": "test/corpus/repos/javascript", - "sha2": "8db9fc5ca6b6b08b797cf0954a326b1d72e32657" + "sha2": "eb0f914082b22114ac7e3a487bec4dae17770ebc" } ,{ "testCaseDescription": "javascript-for-loop-with-in-statement-delete-test", @@ -304,8 +294,7 @@ ] } }, - "summary": "Deleted the 'key in something && i = 0; i < n; i++' for statement", - "tag": "JSONSummary" + "summary": "Deleted the 'key in something && i = 0; i < n; i++' for statement" } ] }, @@ -314,9 +303,9 @@ "filePaths": [ "for-loop-with-in-statement.js" ], - "sha1": "8db9fc5ca6b6b08b797cf0954a326b1d72e32657", + "sha1": "eb0f914082b22114ac7e3a487bec4dae17770ebc", "gitDir": "test/corpus/repos/javascript", - "sha2": "4c3269d570707ef8b45c8660494d318fa4e49614" + "sha2": "d5ae13f5b72c809e77f06665c3eae01cfcf76533" } ,{ "testCaseDescription": "javascript-for-loop-with-in-statement-delete-rest-test", @@ -336,8 +325,7 @@ ] } }, - "summary": "Deleted the 'otherKey in something && i = 0; i < n; i++' for statement", - "tag": "JSONSummary" + "summary": "Deleted the 'otherKey in something && i = 0; i < n; i++' for statement" } ] }, @@ -346,7 +334,7 @@ "filePaths": [ "for-loop-with-in-statement.js" ], - "sha1": "4c3269d570707ef8b45c8660494d318fa4e49614", + "sha1": "d5ae13f5b72c809e77f06665c3eae01cfcf76533", "gitDir": "test/corpus/repos/javascript", - "sha2": "ca4c516f2d2c350b12fd36007d5c8ec2f5d6fe42" + "sha2": "65cf271429cfd2f26c112bf377c0fc4f8d79cba4" }] diff --git a/test/corpus/diff-summaries/javascript/for-of-statement.json b/test/corpus/diff-summaries/javascript/for-of-statement.json index b4bf1a2cb..23caf4e29 100644 --- a/test/corpus/diff-summaries/javascript/for-of-statement.json +++ b/test/corpus/diff-summaries/javascript/for-of-statement.json @@ -16,8 +16,7 @@ ] } }, - "summary": "Added the 'item of items' for statement", - "tag": "JSONSummary" + "summary": "Added the 'item of items' for statement" } ] }, @@ -26,9 +25,9 @@ "filePaths": [ "for-of-statement.js" ], - "sha1": "5079af56f5049cde622a571fb286589b471549e5", + "sha1": "89db44a937a7093bce4f9707fef198d801d1df6c", "gitDir": "test/corpus/repos/javascript", - "sha2": "7897caa7d3f395e6fc8421235775076903bfeea3" + "sha2": "2446083ac07858819361d2b6f4d56e5acb211e1f" } ,{ "testCaseDescription": "javascript-for-of-statement-replacement-insert-test", @@ -48,8 +47,7 @@ ] } }, - "summary": "Added the 'thing of things' for statement", - "tag": "JSONSummary" + "summary": "Added the 'thing of things' for statement" }, { "span": { @@ -64,8 +62,7 @@ ] } }, - "summary": "Added the 'item of items' for statement", - "tag": "JSONSummary" + "summary": "Added the 'item of items' for statement" } ] }, @@ -74,9 +71,9 @@ "filePaths": [ "for-of-statement.js" ], - "sha1": "7897caa7d3f395e6fc8421235775076903bfeea3", + "sha1": "2446083ac07858819361d2b6f4d56e5acb211e1f", "gitDir": "test/corpus/repos/javascript", - "sha2": "764b4aec6e49bf027190ab1e5083bdd35a055279" + "sha2": "3ef3da8fb378a9e3eb0481df414aeebd601a9c58" } ,{ "testCaseDescription": "javascript-for-of-statement-delete-insert-test", @@ -108,8 +105,7 @@ } ] }, - "summary": "Replaced the 'thing' identifier with the 'item' identifier", - "tag": "JSONSummary" + "summary": "Replaced the 'thing' identifier with the 'item' identifier" }, { "span": { @@ -136,8 +132,7 @@ } ] }, - "summary": "Replaced the 'things' identifier with the 'items' identifier", - "tag": "JSONSummary" + "summary": "Replaced the 'things' identifier with the 'items' identifier" }, { "span": { @@ -164,8 +159,7 @@ } ] }, - "summary": "Replaced the 'thing' identifier with the 'item' identifier in the process(item) function call", - "tag": "JSONSummary" + "summary": "Replaced the 'thing' identifier with the 'item' identifier in the process(item) function call" } ] }, @@ -174,9 +168,9 @@ "filePaths": [ "for-of-statement.js" ], - "sha1": "764b4aec6e49bf027190ab1e5083bdd35a055279", + "sha1": "3ef3da8fb378a9e3eb0481df414aeebd601a9c58", "gitDir": "test/corpus/repos/javascript", - "sha2": "ed8939173ee392ec35dd13ff8fee4d4c6f93f985" + "sha2": "27d445ebbe6a2d1428363a86b0d8a72f7c3a1fa7" } ,{ "testCaseDescription": "javascript-for-of-statement-replacement-test", @@ -208,8 +202,7 @@ } ] }, - "summary": "Replaced the 'item' identifier with the 'thing' identifier", - "tag": "JSONSummary" + "summary": "Replaced the 'item' identifier with the 'thing' identifier" }, { "span": { @@ -236,8 +229,7 @@ } ] }, - "summary": "Replaced the 'items' identifier with the 'things' identifier", - "tag": "JSONSummary" + "summary": "Replaced the 'items' identifier with the 'things' identifier" }, { "span": { @@ -264,8 +256,7 @@ } ] }, - "summary": "Replaced the 'item' identifier with the 'thing' identifier in the process(thing) function call", - "tag": "JSONSummary" + "summary": "Replaced the 'item' identifier with the 'thing' identifier in the process(thing) function call" } ] }, @@ -274,9 +265,9 @@ "filePaths": [ "for-of-statement.js" ], - "sha1": "ed8939173ee392ec35dd13ff8fee4d4c6f93f985", + "sha1": "27d445ebbe6a2d1428363a86b0d8a72f7c3a1fa7", "gitDir": "test/corpus/repos/javascript", - "sha2": "8be63f36f0484ba36f2de2a06801fe411b1b6bbc" + "sha2": "7c22bba4de0d72a6896a92034976544f0cf981d9" } ,{ "testCaseDescription": "javascript-for-of-statement-delete-replacement-test", @@ -296,8 +287,7 @@ ] } }, - "summary": "Deleted the 'thing of things' for statement", - "tag": "JSONSummary" + "summary": "Deleted the 'thing of things' for statement" }, { "span": { @@ -312,8 +302,7 @@ ] } }, - "summary": "Deleted the 'item of items' for statement", - "tag": "JSONSummary" + "summary": "Deleted the 'item of items' for statement" }, { "span": { @@ -328,8 +317,7 @@ ] } }, - "summary": "Added the 'thing of things' for statement", - "tag": "JSONSummary" + "summary": "Added the 'thing of things' for statement" } ] }, @@ -338,9 +326,9 @@ "filePaths": [ "for-of-statement.js" ], - "sha1": "8be63f36f0484ba36f2de2a06801fe411b1b6bbc", + "sha1": "7c22bba4de0d72a6896a92034976544f0cf981d9", "gitDir": "test/corpus/repos/javascript", - "sha2": "ae793daccac506e88da2f1d9e5bbe6a63f0c57e8" + "sha2": "9a4e4fb16b79c73d23f19d5e01de22370f426681" } ,{ "testCaseDescription": "javascript-for-of-statement-delete-test", @@ -360,8 +348,7 @@ ] } }, - "summary": "Deleted the 'item of items' for statement", - "tag": "JSONSummary" + "summary": "Deleted the 'item of items' for statement" } ] }, @@ -370,9 +357,9 @@ "filePaths": [ "for-of-statement.js" ], - "sha1": "ae793daccac506e88da2f1d9e5bbe6a63f0c57e8", + "sha1": "9a4e4fb16b79c73d23f19d5e01de22370f426681", "gitDir": "test/corpus/repos/javascript", - "sha2": "99cbdc5330a41c478311d2cdf679409e67ebb255" + "sha2": "cf9946632e343e7067c51a06f3e18f62fabbdb54" } ,{ "testCaseDescription": "javascript-for-of-statement-delete-rest-test", @@ -392,8 +379,7 @@ ] } }, - "summary": "Deleted the 'thing of things' for statement", - "tag": "JSONSummary" + "summary": "Deleted the 'thing of things' for statement" } ] }, @@ -402,7 +388,7 @@ "filePaths": [ "for-of-statement.js" ], - "sha1": "99cbdc5330a41c478311d2cdf679409e67ebb255", + "sha1": "cf9946632e343e7067c51a06f3e18f62fabbdb54", "gitDir": "test/corpus/repos/javascript", - "sha2": "c1166aa59e4b025c51e2a166a47413eba325ff1d" + "sha2": "67ef9e8da7b64fdbdf370b43e4c780e28ae9efdf" }] diff --git a/test/corpus/diff-summaries/javascript/for-statement.json b/test/corpus/diff-summaries/javascript/for-statement.json index 09203b51e..e4c05b216 100644 --- a/test/corpus/diff-summaries/javascript/for-statement.json +++ b/test/corpus/diff-summaries/javascript/for-statement.json @@ -16,8 +16,7 @@ ] } }, - "summary": "Added the 'i = 0, init(); i < 10; i++' for statement", - "tag": "JSONSummary" + "summary": "Added the 'i = 0, init(); i < 10; i++' for statement" } ] }, @@ -26,9 +25,9 @@ "filePaths": [ "for-statement.js" ], - "sha1": "758306debb6130fc8710a0ff09833d692791db56", + "sha1": "de443cf00be9a98ac907413bfb98ae7b8db27831", "gitDir": "test/corpus/repos/javascript", - "sha2": "00bf00e6840e200b9b83516547c531a2ff3898b1" + "sha2": "ee7de8213f031a170e082ef6e72ed09cb1c78ddd" } ,{ "testCaseDescription": "javascript-for-statement-replacement-insert-test", @@ -48,8 +47,7 @@ ] } }, - "summary": "Added the 'i = 0, init(); i < 100; i++' for statement", - "tag": "JSONSummary" + "summary": "Added the 'i = 0, init(); i < 100; i++' for statement" }, { "span": { @@ -64,8 +62,7 @@ ] } }, - "summary": "Added the 'i = 0, init(); i < 10; i++' for statement", - "tag": "JSONSummary" + "summary": "Added the 'i = 0, init(); i < 10; i++' for statement" } ] }, @@ -74,9 +71,9 @@ "filePaths": [ "for-statement.js" ], - "sha1": "00bf00e6840e200b9b83516547c531a2ff3898b1", + "sha1": "ee7de8213f031a170e082ef6e72ed09cb1c78ddd", "gitDir": "test/corpus/repos/javascript", - "sha2": "0b2091d8a227a635eb9bb3aa3ce14b284b77180a" + "sha2": "3561a122a3823f4dae34a38b8308a08c84dd96f8" } ,{ "testCaseDescription": "javascript-for-statement-delete-insert-test", @@ -108,8 +105,7 @@ } ] }, - "summary": "Replaced '100' with '10'", - "tag": "JSONSummary" + "summary": "Replaced '100' with '10'" } ] }, @@ -118,9 +114,9 @@ "filePaths": [ "for-statement.js" ], - "sha1": "0b2091d8a227a635eb9bb3aa3ce14b284b77180a", + "sha1": "3561a122a3823f4dae34a38b8308a08c84dd96f8", "gitDir": "test/corpus/repos/javascript", - "sha2": "27c0f25dae543a46ab393cf49fc8202434805502" + "sha2": "45cc625c20823056b697a08119111b3849855d04" } ,{ "testCaseDescription": "javascript-for-statement-replacement-test", @@ -152,8 +148,7 @@ } ] }, - "summary": "Replaced '10' with '100'", - "tag": "JSONSummary" + "summary": "Replaced '10' with '100'" } ] }, @@ -162,9 +157,9 @@ "filePaths": [ "for-statement.js" ], - "sha1": "27c0f25dae543a46ab393cf49fc8202434805502", + "sha1": "45cc625c20823056b697a08119111b3849855d04", "gitDir": "test/corpus/repos/javascript", - "sha2": "7696ee1c7f9e18ee1117c40c2d37d07a11f1f5df" + "sha2": "634af4fd56a8cb4fb227f1505cad159b0aab1036" } ,{ "testCaseDescription": "javascript-for-statement-delete-replacement-test", @@ -184,8 +179,7 @@ ] } }, - "summary": "Deleted the 'i = 0, init(); i < 100; i++' for statement", - "tag": "JSONSummary" + "summary": "Deleted the 'i = 0, init(); i < 100; i++' for statement" }, { "span": { @@ -200,8 +194,7 @@ ] } }, - "summary": "Deleted the 'i = 0, init(); i < 10; i++' for statement", - "tag": "JSONSummary" + "summary": "Deleted the 'i = 0, init(); i < 10; i++' for statement" }, { "span": { @@ -216,8 +209,7 @@ ] } }, - "summary": "Added the 'i = 0, init(); i < 100; i++' for statement", - "tag": "JSONSummary" + "summary": "Added the 'i = 0, init(); i < 100; i++' for statement" } ] }, @@ -226,9 +218,9 @@ "filePaths": [ "for-statement.js" ], - "sha1": "7696ee1c7f9e18ee1117c40c2d37d07a11f1f5df", + "sha1": "634af4fd56a8cb4fb227f1505cad159b0aab1036", "gitDir": "test/corpus/repos/javascript", - "sha2": "4a93852bc579797f9f5de1e47fce59cfc8b2497f" + "sha2": "ae4347d2058f6cd47934f4b95215446aaa82b749" } ,{ "testCaseDescription": "javascript-for-statement-delete-test", @@ -248,8 +240,7 @@ ] } }, - "summary": "Deleted the 'i = 0, init(); i < 10; i++' for statement", - "tag": "JSONSummary" + "summary": "Deleted the 'i = 0, init(); i < 10; i++' for statement" } ] }, @@ -258,9 +249,9 @@ "filePaths": [ "for-statement.js" ], - "sha1": "4a93852bc579797f9f5de1e47fce59cfc8b2497f", + "sha1": "ae4347d2058f6cd47934f4b95215446aaa82b749", "gitDir": "test/corpus/repos/javascript", - "sha2": "c1968c262d5b3c83c9187948709acbbc9f620462" + "sha2": "aa911951d4d68356f23d3090ab0bddf3d9f5c6f1" } ,{ "testCaseDescription": "javascript-for-statement-delete-rest-test", @@ -280,8 +271,7 @@ ] } }, - "summary": "Deleted the 'i = 0, init(); i < 100; i++' for statement", - "tag": "JSONSummary" + "summary": "Deleted the 'i = 0, init(); i < 100; i++' for statement" } ] }, @@ -290,7 +280,7 @@ "filePaths": [ "for-statement.js" ], - "sha1": "c1968c262d5b3c83c9187948709acbbc9f620462", + "sha1": "aa911951d4d68356f23d3090ab0bddf3d9f5c6f1", "gitDir": "test/corpus/repos/javascript", - "sha2": "d7c7a2ed324c7355ba6fc63705b6b879afd92c14" + "sha2": "4e9ef9bf5e742b75d10cac3498f637ab763b6c99" }] diff --git a/test/corpus/diff-summaries/javascript/function-call-args.json b/test/corpus/diff-summaries/javascript/function-call-args.json index 7b7b03051..3713d4d2d 100644 --- a/test/corpus/diff-summaries/javascript/function-call-args.json +++ b/test/corpus/diff-summaries/javascript/function-call-args.json @@ -16,8 +16,7 @@ ] } }, - "summary": "Added the 'someFunction(1, \"string\", …, true)' function call", - "tag": "JSONSummary" + "summary": "Added the 'someFunction(1, \"string\", …, true)' function call" } ] }, @@ -26,9 +25,9 @@ "filePaths": [ "function-call-args.js" ], - "sha1": "39371fc387de287b5fed01670ecb6d42834d9558", + "sha1": "667c51b29a73971928a1be313c249304f3828099", "gitDir": "test/corpus/repos/javascript", - "sha2": "b7a3a181908a1f263066ded0b6ffd54f76caf38f" + "sha2": "192575f8455ac438aa0cbfab74d84d4183377778" } ,{ "testCaseDescription": "javascript-function-call-args-replacement-insert-test", @@ -48,8 +47,7 @@ ] } }, - "summary": "Added the 'someFunction(1, \"otherString\", …, false)' function call", - "tag": "JSONSummary" + "summary": "Added the 'someFunction(1, \"otherString\", …, false)' function call" }, { "span": { @@ -64,8 +62,7 @@ ] } }, - "summary": "Added the 'someFunction(1, \"string\", …, true)' function call", - "tag": "JSONSummary" + "summary": "Added the 'someFunction(1, \"string\", …, true)' function call" } ] }, @@ -74,9 +71,9 @@ "filePaths": [ "function-call-args.js" ], - "sha1": "b7a3a181908a1f263066ded0b6ffd54f76caf38f", + "sha1": "192575f8455ac438aa0cbfab74d84d4183377778", "gitDir": "test/corpus/repos/javascript", - "sha2": "c0233e25160450709ba8e3b1e9b3c728816e329f" + "sha2": "1acb1db7befa63bf81039b1201e46d1c93f89aa6" } ,{ "testCaseDescription": "javascript-function-call-args-delete-insert-test", @@ -108,8 +105,7 @@ } ] }, - "summary": "Replaced the \"otherString\" string with the \"string\" string in the someFunction(1, \"string\", …, true) function call", - "tag": "JSONSummary" + "summary": "Replaced the \"otherString\" string with the \"string\" string in the someFunction(1, \"string\", …, true) function call" }, { "span": { @@ -136,8 +132,7 @@ } ] }, - "summary": "Replaced the 'b' identifier with the 'a' identifier in the someFunction(1, \"string\", …, true) function call", - "tag": "JSONSummary" + "summary": "Replaced the 'b' identifier with the 'a' identifier in the someFunction(1, \"string\", …, true) function call" }, { "span": { @@ -164,8 +159,7 @@ } ] }, - "summary": "Replaced the 'c' identifier with the 'b' identifier in the someFunction(1, \"string\", …, true) function call", - "tag": "JSONSummary" + "summary": "Replaced the 'c' identifier with the 'b' identifier in the someFunction(1, \"string\", …, true) function call" }, { "span": { @@ -192,8 +186,7 @@ } ] }, - "summary": "Replaced the 'b' identifier with the 'a' identifier in the console.log(a) method call", - "tag": "JSONSummary" + "summary": "Replaced the 'b' identifier with the 'a' identifier in the console.log(a) method call" }, { "span": { @@ -220,8 +213,7 @@ } ] }, - "summary": "Replaced the 'c' identifier with the 'b' identifier in the someFunction(1, \"string\", …, true) function call", - "tag": "JSONSummary" + "summary": "Replaced the 'c' identifier with the 'b' identifier in the someFunction(1, \"string\", …, true) function call" }, { "span": { @@ -248,8 +240,7 @@ } ] }, - "summary": "Replaced 'false' with 'true' in the someFunction(1, \"string\", …, true) function call", - "tag": "JSONSummary" + "summary": "Replaced 'false' with 'true' in the someFunction(1, \"string\", …, true) function call" } ] }, @@ -258,9 +249,9 @@ "filePaths": [ "function-call-args.js" ], - "sha1": "c0233e25160450709ba8e3b1e9b3c728816e329f", + "sha1": "1acb1db7befa63bf81039b1201e46d1c93f89aa6", "gitDir": "test/corpus/repos/javascript", - "sha2": "ec2a13df058c25b9f4e873aeef08c968213e3a30" + "sha2": "1ef1f93e8742c827b5e36dce1b2a58d084940f00" } ,{ "testCaseDescription": "javascript-function-call-args-replacement-test", @@ -292,8 +283,7 @@ } ] }, - "summary": "Replaced the \"string\" string with the \"otherString\" string in the someFunction(1, \"otherString\", …, false) function call", - "tag": "JSONSummary" + "summary": "Replaced the \"string\" string with the \"otherString\" string in the someFunction(1, \"otherString\", …, false) function call" }, { "span": { @@ -320,8 +310,7 @@ } ] }, - "summary": "Replaced the 'a' identifier with the 'b' identifier in the someFunction(1, \"otherString\", …, false) function call", - "tag": "JSONSummary" + "summary": "Replaced the 'a' identifier with the 'b' identifier in the someFunction(1, \"otherString\", …, false) function call" }, { "span": { @@ -348,8 +337,7 @@ } ] }, - "summary": "Replaced the 'b' identifier with the 'c' identifier in the someFunction(1, \"otherString\", …, false) function call", - "tag": "JSONSummary" + "summary": "Replaced the 'b' identifier with the 'c' identifier in the someFunction(1, \"otherString\", …, false) function call" }, { "span": { @@ -376,8 +364,7 @@ } ] }, - "summary": "Replaced the 'a' identifier with the 'b' identifier in the console.log(b) method call", - "tag": "JSONSummary" + "summary": "Replaced the 'a' identifier with the 'b' identifier in the console.log(b) method call" }, { "span": { @@ -404,8 +391,7 @@ } ] }, - "summary": "Replaced the 'b' identifier with the 'c' identifier in the someFunction(1, \"otherString\", …, false) function call", - "tag": "JSONSummary" + "summary": "Replaced the 'b' identifier with the 'c' identifier in the someFunction(1, \"otherString\", …, false) function call" }, { "span": { @@ -432,8 +418,7 @@ } ] }, - "summary": "Replaced 'true' with 'false' in the someFunction(1, \"otherString\", …, false) function call", - "tag": "JSONSummary" + "summary": "Replaced 'true' with 'false' in the someFunction(1, \"otherString\", …, false) function call" } ] }, @@ -442,9 +427,9 @@ "filePaths": [ "function-call-args.js" ], - "sha1": "ec2a13df058c25b9f4e873aeef08c968213e3a30", + "sha1": "1ef1f93e8742c827b5e36dce1b2a58d084940f00", "gitDir": "test/corpus/repos/javascript", - "sha2": "2a065e7cc65868acd59182dd9ee7aa71f581be6f" + "sha2": "9610dd7ef8edff8b65d81c889cb22aa5efb67019" } ,{ "testCaseDescription": "javascript-function-call-args-delete-replacement-test", @@ -464,8 +449,7 @@ ] } }, - "summary": "Deleted the 'someFunction(1, \"otherString\", …, false)' function call", - "tag": "JSONSummary" + "summary": "Deleted the 'someFunction(1, \"otherString\", …, false)' function call" }, { "span": { @@ -480,8 +464,7 @@ ] } }, - "summary": "Deleted the 'someFunction(1, \"string\", …, true)' function call", - "tag": "JSONSummary" + "summary": "Deleted the 'someFunction(1, \"string\", …, true)' function call" }, { "span": { @@ -496,8 +479,7 @@ ] } }, - "summary": "Added the 'someFunction(1, \"otherString\", …, false)' function call", - "tag": "JSONSummary" + "summary": "Added the 'someFunction(1, \"otherString\", …, false)' function call" } ] }, @@ -506,9 +488,9 @@ "filePaths": [ "function-call-args.js" ], - "sha1": "2a065e7cc65868acd59182dd9ee7aa71f581be6f", + "sha1": "9610dd7ef8edff8b65d81c889cb22aa5efb67019", "gitDir": "test/corpus/repos/javascript", - "sha2": "b56a80a0b9ce5ff95b4ec2417ff4770ac5d7d5b5" + "sha2": "ad2d4d347fb4551d07b8970a27634569e6f9b789" } ,{ "testCaseDescription": "javascript-function-call-args-delete-test", @@ -528,8 +510,7 @@ ] } }, - "summary": "Deleted the 'someFunction(1, \"string\", …, true)' function call", - "tag": "JSONSummary" + "summary": "Deleted the 'someFunction(1, \"string\", …, true)' function call" } ] }, @@ -538,9 +519,9 @@ "filePaths": [ "function-call-args.js" ], - "sha1": "b56a80a0b9ce5ff95b4ec2417ff4770ac5d7d5b5", + "sha1": "ad2d4d347fb4551d07b8970a27634569e6f9b789", "gitDir": "test/corpus/repos/javascript", - "sha2": "202a515a4ca63fa61a58a82ea1d5bcd10515da8c" + "sha2": "953921a66be0d1ed61bf4db6884cd0ad0a057f07" } ,{ "testCaseDescription": "javascript-function-call-args-delete-rest-test", @@ -560,8 +541,7 @@ ] } }, - "summary": "Deleted the 'someFunction(1, \"otherString\", …, false)' function call", - "tag": "JSONSummary" + "summary": "Deleted the 'someFunction(1, \"otherString\", …, false)' function call" } ] }, @@ -570,7 +550,7 @@ "filePaths": [ "function-call-args.js" ], - "sha1": "202a515a4ca63fa61a58a82ea1d5bcd10515da8c", + "sha1": "953921a66be0d1ed61bf4db6884cd0ad0a057f07", "gitDir": "test/corpus/repos/javascript", - "sha2": "989abe2f89480b24702666d42becea8aa3dd9356" + "sha2": "6f3b3d0ccb1f85f9dd79220ea588b11e540d7290" }] diff --git a/test/corpus/diff-summaries/javascript/function-call.json b/test/corpus/diff-summaries/javascript/function-call.json index 9c1b4df40..42bb0859e 100644 --- a/test/corpus/diff-summaries/javascript/function-call.json +++ b/test/corpus/diff-summaries/javascript/function-call.json @@ -16,8 +16,7 @@ ] } }, - "summary": "Added the 'someFunction(arg1, \"arg2\")' function call", - "tag": "JSONSummary" + "summary": "Added the 'someFunction(arg1, \"arg2\")' function call" } ] }, @@ -26,9 +25,9 @@ "filePaths": [ "function-call.js" ], - "sha1": "2920543b3620bcf0c44e9f14e9b9173b7ffaaf74", + "sha1": "4b213c3b88b5e8aace51dfa0379aaa8de01536b8", "gitDir": "test/corpus/repos/javascript", - "sha2": "7fb60101d44227f815b26e0ddf7192c814147c0a" + "sha2": "77cb0c7af7488197be59308f1296a909bd4dc5b6" } ,{ "testCaseDescription": "javascript-function-call-replacement-insert-test", @@ -48,8 +47,7 @@ ] } }, - "summary": "Added the 'someFunction(arg1, \"arg3\")' function call", - "tag": "JSONSummary" + "summary": "Added the 'someFunction(arg1, \"arg3\")' function call" }, { "span": { @@ -64,8 +62,7 @@ ] } }, - "summary": "Added the 'someFunction(arg1, \"arg2\")' function call", - "tag": "JSONSummary" + "summary": "Added the 'someFunction(arg1, \"arg2\")' function call" } ] }, @@ -74,9 +71,9 @@ "filePaths": [ "function-call.js" ], - "sha1": "7fb60101d44227f815b26e0ddf7192c814147c0a", + "sha1": "77cb0c7af7488197be59308f1296a909bd4dc5b6", "gitDir": "test/corpus/repos/javascript", - "sha2": "b8ef71202991eb150947127c3d627dfefbfb9cbd" + "sha2": "1b4585f4d837d2412aa2349b729616df4be4dfc3" } ,{ "testCaseDescription": "javascript-function-call-delete-insert-test", @@ -108,8 +105,7 @@ } ] }, - "summary": "Replaced the \"arg3\" string with the \"arg2\" string in the someFunction(arg1, \"arg2\") function call", - "tag": "JSONSummary" + "summary": "Replaced the \"arg3\" string with the \"arg2\" string in the someFunction(arg1, \"arg2\") function call" } ] }, @@ -118,9 +114,9 @@ "filePaths": [ "function-call.js" ], - "sha1": "b8ef71202991eb150947127c3d627dfefbfb9cbd", + "sha1": "1b4585f4d837d2412aa2349b729616df4be4dfc3", "gitDir": "test/corpus/repos/javascript", - "sha2": "1c6634e5803e9eae248fb104c87d95b7ca4911f3" + "sha2": "ff9cd97499db7659134fc3f9c3eede631ffcf43b" } ,{ "testCaseDescription": "javascript-function-call-replacement-test", @@ -152,8 +148,7 @@ } ] }, - "summary": "Replaced the \"arg2\" string with the \"arg3\" string in the someFunction(arg1, \"arg3\") function call", - "tag": "JSONSummary" + "summary": "Replaced the \"arg2\" string with the \"arg3\" string in the someFunction(arg1, \"arg3\") function call" } ] }, @@ -162,9 +157,9 @@ "filePaths": [ "function-call.js" ], - "sha1": "1c6634e5803e9eae248fb104c87d95b7ca4911f3", + "sha1": "ff9cd97499db7659134fc3f9c3eede631ffcf43b", "gitDir": "test/corpus/repos/javascript", - "sha2": "89d68d8b51fcfcf79005c5616ee95351c6eb9d61" + "sha2": "40ae68e40bb296a0fed10ad139a32c0bdd48c91d" } ,{ "testCaseDescription": "javascript-function-call-delete-replacement-test", @@ -184,8 +179,7 @@ ] } }, - "summary": "Deleted the 'someFunction(arg1, \"arg3\")' function call", - "tag": "JSONSummary" + "summary": "Deleted the 'someFunction(arg1, \"arg3\")' function call" }, { "span": { @@ -200,8 +194,7 @@ ] } }, - "summary": "Deleted the 'someFunction(arg1, \"arg2\")' function call", - "tag": "JSONSummary" + "summary": "Deleted the 'someFunction(arg1, \"arg2\")' function call" }, { "span": { @@ -216,8 +209,7 @@ ] } }, - "summary": "Added the 'someFunction(arg1, \"arg3\")' function call", - "tag": "JSONSummary" + "summary": "Added the 'someFunction(arg1, \"arg3\")' function call" } ] }, @@ -226,9 +218,9 @@ "filePaths": [ "function-call.js" ], - "sha1": "89d68d8b51fcfcf79005c5616ee95351c6eb9d61", + "sha1": "40ae68e40bb296a0fed10ad139a32c0bdd48c91d", "gitDir": "test/corpus/repos/javascript", - "sha2": "25b62ac788457989d53e49e35e947be2120e91d4" + "sha2": "97b784a48b8ba2ab17d9fb5e690fdd5e27995053" } ,{ "testCaseDescription": "javascript-function-call-delete-test", @@ -248,8 +240,7 @@ ] } }, - "summary": "Deleted the 'someFunction(arg1, \"arg2\")' function call", - "tag": "JSONSummary" + "summary": "Deleted the 'someFunction(arg1, \"arg2\")' function call" } ] }, @@ -258,9 +249,9 @@ "filePaths": [ "function-call.js" ], - "sha1": "25b62ac788457989d53e49e35e947be2120e91d4", + "sha1": "97b784a48b8ba2ab17d9fb5e690fdd5e27995053", "gitDir": "test/corpus/repos/javascript", - "sha2": "d67336b7b60950bf99ef6777a6d25cd8a6cb57a6" + "sha2": "4ab24690a7b34511675eb6c179c5b85a382c7952" } ,{ "testCaseDescription": "javascript-function-call-delete-rest-test", @@ -280,8 +271,7 @@ ] } }, - "summary": "Deleted the 'someFunction(arg1, \"arg3\")' function call", - "tag": "JSONSummary" + "summary": "Deleted the 'someFunction(arg1, \"arg3\")' function call" } ] }, @@ -290,7 +280,7 @@ "filePaths": [ "function-call.js" ], - "sha1": "d67336b7b60950bf99ef6777a6d25cd8a6cb57a6", + "sha1": "4ab24690a7b34511675eb6c179c5b85a382c7952", "gitDir": "test/corpus/repos/javascript", - "sha2": "b0e9ef95e61d208d86142a5e5682fe30ceb18c8b" + "sha2": "35a769b31d29eac1dc0307402e6e2698e71177ac" }] diff --git a/test/corpus/diff-summaries/javascript/function.json b/test/corpus/diff-summaries/javascript/function.json index efa80ebab..e0d0f55e5 100644 --- a/test/corpus/diff-summaries/javascript/function.json +++ b/test/corpus/diff-summaries/javascript/function.json @@ -16,8 +16,7 @@ ] } }, - "summary": "Added an anonymous(arg1, arg2) function", - "tag": "JSONSummary" + "summary": "Added an anonymous(arg1, arg2) function" } ] }, @@ -26,9 +25,9 @@ "filePaths": [ "function.js" ], - "sha1": "67cbf8843e0286f8dda242b238d30efab57d6790", + "sha1": "9cd120dd3b152d83f8eea69dfe22940d1acbf177", "gitDir": "test/corpus/repos/javascript", - "sha2": "2717b5aa509e14dfd94842eea00ca66111a015be" + "sha2": "654ce2cc1260f48fb82edbd0cc5926f11c877700" } ,{ "testCaseDescription": "javascript-function-replacement-insert-test", @@ -48,8 +47,7 @@ ] } }, - "summary": "Added an anonymous(arg1, arg2) function", - "tag": "JSONSummary" + "summary": "Added an anonymous(arg1, arg2) function" }, { "span": { @@ -64,8 +62,7 @@ ] } }, - "summary": "Added an anonymous(arg1, arg2) function", - "tag": "JSONSummary" + "summary": "Added an anonymous(arg1, arg2) function" } ] }, @@ -74,9 +71,9 @@ "filePaths": [ "function.js" ], - "sha1": "2717b5aa509e14dfd94842eea00ca66111a015be", + "sha1": "654ce2cc1260f48fb82edbd0cc5926f11c877700", "gitDir": "test/corpus/repos/javascript", - "sha2": "f98962b37651faa3154d25fe2828a12df02992d8" + "sha2": "d935758b74f8e47e1475010591b39e545d5ecc7a" } ,{ "testCaseDescription": "javascript-function-delete-insert-test", @@ -108,8 +105,7 @@ } ] }, - "summary": "Replaced the 'arg1' identifier with the 'arg2' identifier", - "tag": "JSONSummary" + "summary": "Replaced the 'arg1' identifier with the 'arg2' identifier" } ] }, @@ -118,9 +114,9 @@ "filePaths": [ "function.js" ], - "sha1": "f98962b37651faa3154d25fe2828a12df02992d8", + "sha1": "d935758b74f8e47e1475010591b39e545d5ecc7a", "gitDir": "test/corpus/repos/javascript", - "sha2": "2b9d37d0871a1c8f0a50842e50cab572f55d07db" + "sha2": "8c1abbc8823d22df989efd04e0bcc27c2342b00d" } ,{ "testCaseDescription": "javascript-function-replacement-test", @@ -152,8 +148,7 @@ } ] }, - "summary": "Replaced the 'arg2' identifier with the 'arg1' identifier", - "tag": "JSONSummary" + "summary": "Replaced the 'arg2' identifier with the 'arg1' identifier" } ] }, @@ -162,9 +157,9 @@ "filePaths": [ "function.js" ], - "sha1": "2b9d37d0871a1c8f0a50842e50cab572f55d07db", + "sha1": "8c1abbc8823d22df989efd04e0bcc27c2342b00d", "gitDir": "test/corpus/repos/javascript", - "sha2": "1bec33037691d4c4d97117aa1a1550a1a0d3113f" + "sha2": "0dbbe59af8673a1a5d7ef30f3feed1d050360f91" } ,{ "testCaseDescription": "javascript-function-delete-replacement-test", @@ -184,8 +179,7 @@ ] } }, - "summary": "Deleted an anonymous(arg1, arg2) function", - "tag": "JSONSummary" + "summary": "Deleted an anonymous(arg1, arg2) function" }, { "span": { @@ -200,8 +194,7 @@ ] } }, - "summary": "Deleted an anonymous(arg1, arg2) function", - "tag": "JSONSummary" + "summary": "Deleted an anonymous(arg1, arg2) function" }, { "span": { @@ -216,8 +209,7 @@ ] } }, - "summary": "Added an anonymous(arg1, arg2) function", - "tag": "JSONSummary" + "summary": "Added an anonymous(arg1, arg2) function" } ] }, @@ -226,9 +218,9 @@ "filePaths": [ "function.js" ], - "sha1": "1bec33037691d4c4d97117aa1a1550a1a0d3113f", + "sha1": "0dbbe59af8673a1a5d7ef30f3feed1d050360f91", "gitDir": "test/corpus/repos/javascript", - "sha2": "189c17d7869e4ec45865288472d5616e6f934389" + "sha2": "aae7da5266e45976f3617b3d9068bbba2b814869" } ,{ "testCaseDescription": "javascript-function-delete-test", @@ -248,8 +240,7 @@ ] } }, - "summary": "Deleted an anonymous(arg1, arg2) function", - "tag": "JSONSummary" + "summary": "Deleted an anonymous(arg1, arg2) function" } ] }, @@ -258,9 +249,9 @@ "filePaths": [ "function.js" ], - "sha1": "189c17d7869e4ec45865288472d5616e6f934389", + "sha1": "aae7da5266e45976f3617b3d9068bbba2b814869", "gitDir": "test/corpus/repos/javascript", - "sha2": "54e8366ab2c4558cf28dd50f6939ae84738caa6c" + "sha2": "183393122ec9e9b0bc8b67482c0435aec3fa76a6" } ,{ "testCaseDescription": "javascript-function-delete-rest-test", @@ -280,8 +271,7 @@ ] } }, - "summary": "Deleted an anonymous(arg1, arg2) function", - "tag": "JSONSummary" + "summary": "Deleted an anonymous(arg1, arg2) function" } ] }, @@ -290,7 +280,7 @@ "filePaths": [ "function.js" ], - "sha1": "54e8366ab2c4558cf28dd50f6939ae84738caa6c", + "sha1": "183393122ec9e9b0bc8b67482c0435aec3fa76a6", "gitDir": "test/corpus/repos/javascript", - "sha2": "ea75c493779d6c65e44c59733f6073e0be814d0b" + "sha2": "f0f1ee84b62e5f9e91523c1e29c3469ab06fefdf" }] diff --git a/test/corpus/diff-summaries/javascript/generator-function.json b/test/corpus/diff-summaries/javascript/generator-function.json index fd2584efb..0ca4a41bd 100644 --- a/test/corpus/diff-summaries/javascript/generator-function.json +++ b/test/corpus/diff-summaries/javascript/generator-function.json @@ -16,8 +16,7 @@ ] } }, - "summary": "Added the 'generateStuff' function", - "tag": "JSONSummary" + "summary": "Added the 'generateStuff' function" } ] }, @@ -26,9 +25,9 @@ "filePaths": [ "generator-function.js" ], - "sha1": "4e58cc6cacea1897b6ba0b9d766f0ba965b0c8fa", + "sha1": "5190dfa16aab4d1416b5dad47a3f9cc704af1fae", "gitDir": "test/corpus/repos/javascript", - "sha2": "18a0e0a3a3ce01a9032d344cc27e74ceb4ca309f" + "sha2": "d7eb5084f8ee88c7b9f3657c9c05d72e4329c5c7" } ,{ "testCaseDescription": "javascript-generator-function-replacement-insert-test", @@ -48,8 +47,7 @@ ] } }, - "summary": "Added the 'generateNewStuff' function", - "tag": "JSONSummary" + "summary": "Added the 'generateNewStuff' function" }, { "span": { @@ -64,8 +62,7 @@ ] } }, - "summary": "Added the 'generateStuff' function", - "tag": "JSONSummary" + "summary": "Added the 'generateStuff' function" } ] }, @@ -74,9 +71,9 @@ "filePaths": [ "generator-function.js" ], - "sha1": "18a0e0a3a3ce01a9032d344cc27e74ceb4ca309f", + "sha1": "d7eb5084f8ee88c7b9f3657c9c05d72e4329c5c7", "gitDir": "test/corpus/repos/javascript", - "sha2": "23285112861e1d2fe617efdb23c5d51bf4075224" + "sha2": "9a1ba4ab7ac42607d9eacb0e871763a2bfe06221" } ,{ "testCaseDescription": "javascript-generator-function-delete-insert-test", @@ -108,8 +105,7 @@ } ] }, - "summary": "Replaced the 'generateNewStuff' identifier with the 'generateStuff' identifier in the generateStuff function", - "tag": "JSONSummary" + "summary": "Replaced the 'generateNewStuff' identifier with the 'generateStuff' identifier in the generateStuff function" } ] }, @@ -118,9 +114,9 @@ "filePaths": [ "generator-function.js" ], - "sha1": "23285112861e1d2fe617efdb23c5d51bf4075224", + "sha1": "9a1ba4ab7ac42607d9eacb0e871763a2bfe06221", "gitDir": "test/corpus/repos/javascript", - "sha2": "3cd99e8cbe1ba540886b65b6921ec1cf01fb79ca" + "sha2": "7ed14c167f2304005ed80d19a4019dfe9b3d9818" } ,{ "testCaseDescription": "javascript-generator-function-replacement-test", @@ -152,8 +148,7 @@ } ] }, - "summary": "Replaced the 'generateStuff' identifier with the 'generateNewStuff' identifier in the generateNewStuff function", - "tag": "JSONSummary" + "summary": "Replaced the 'generateStuff' identifier with the 'generateNewStuff' identifier in the generateNewStuff function" } ] }, @@ -162,9 +157,9 @@ "filePaths": [ "generator-function.js" ], - "sha1": "3cd99e8cbe1ba540886b65b6921ec1cf01fb79ca", + "sha1": "7ed14c167f2304005ed80d19a4019dfe9b3d9818", "gitDir": "test/corpus/repos/javascript", - "sha2": "afe62cf42a38e09a30d1e289c2197445039c4d8b" + "sha2": "fd15cd2ea8a79ab44aefbe49e0cefa5d77567210" } ,{ "testCaseDescription": "javascript-generator-function-delete-replacement-test", @@ -184,8 +179,7 @@ ] } }, - "summary": "Deleted the 'generateNewStuff' function", - "tag": "JSONSummary" + "summary": "Deleted the 'generateNewStuff' function" }, { "span": { @@ -200,8 +194,7 @@ ] } }, - "summary": "Deleted the 'generateStuff' function", - "tag": "JSONSummary" + "summary": "Deleted the 'generateStuff' function" }, { "span": { @@ -216,8 +209,7 @@ ] } }, - "summary": "Added the 'generateNewStuff' function", - "tag": "JSONSummary" + "summary": "Added the 'generateNewStuff' function" } ] }, @@ -226,9 +218,9 @@ "filePaths": [ "generator-function.js" ], - "sha1": "afe62cf42a38e09a30d1e289c2197445039c4d8b", + "sha1": "fd15cd2ea8a79ab44aefbe49e0cefa5d77567210", "gitDir": "test/corpus/repos/javascript", - "sha2": "b8554280a32f48d22eff39b921432c8148f2e602" + "sha2": "f7461e2154cb8c35bd33d73880ac8ce6fed13968" } ,{ "testCaseDescription": "javascript-generator-function-delete-test", @@ -248,8 +240,7 @@ ] } }, - "summary": "Deleted the 'generateStuff' function", - "tag": "JSONSummary" + "summary": "Deleted the 'generateStuff' function" } ] }, @@ -258,9 +249,9 @@ "filePaths": [ "generator-function.js" ], - "sha1": "b8554280a32f48d22eff39b921432c8148f2e602", + "sha1": "f7461e2154cb8c35bd33d73880ac8ce6fed13968", "gitDir": "test/corpus/repos/javascript", - "sha2": "015cdf9ee2145bcf4de97926d0df3d30f5f4b23e" + "sha2": "d6e72611d7be249f33d8283e3fd246ba10119a64" } ,{ "testCaseDescription": "javascript-generator-function-delete-rest-test", @@ -280,8 +271,7 @@ ] } }, - "summary": "Deleted the 'generateNewStuff' function", - "tag": "JSONSummary" + "summary": "Deleted the 'generateNewStuff' function" } ] }, @@ -290,7 +280,7 @@ "filePaths": [ "generator-function.js" ], - "sha1": "015cdf9ee2145bcf4de97926d0df3d30f5f4b23e", + "sha1": "d6e72611d7be249f33d8283e3fd246ba10119a64", "gitDir": "test/corpus/repos/javascript", - "sha2": "bb0f797d0ecd6410261347f4bb4a9d7ec2dbd9e8" + "sha2": "dac1b3637553f83bfd1567e914a0236f9b41b9ec" }] diff --git a/test/corpus/diff-summaries/javascript/identifier.json b/test/corpus/diff-summaries/javascript/identifier.json index 553b940e7..d684cde62 100644 --- a/test/corpus/diff-summaries/javascript/identifier.json +++ b/test/corpus/diff-summaries/javascript/identifier.json @@ -16,8 +16,7 @@ ] } }, - "summary": "Added the 'theVar' identifier", - "tag": "JSONSummary" + "summary": "Added the 'theVar' identifier" } ] }, @@ -26,9 +25,9 @@ "filePaths": [ "identifier.js" ], - "sha1": "326c0b42a3c17cfb9c231515f4cbe3c81c621f1c", + "sha1": "49074a4800a61fa651152d1ed712c66519fafbeb", "gitDir": "test/corpus/repos/javascript", - "sha2": "820fa9e9590b2599eceae072c5f58cdbdb9a537c" + "sha2": "7c6643be086c41a5cd376fbf7b36e2f7d33bc1bf" } ,{ "testCaseDescription": "javascript-identifier-replacement-insert-test", @@ -48,8 +47,7 @@ ] } }, - "summary": "Added the 'theVar2' identifier", - "tag": "JSONSummary" + "summary": "Added the 'theVar2' identifier" }, { "span": { @@ -64,8 +62,7 @@ ] } }, - "summary": "Added the 'theVar' identifier", - "tag": "JSONSummary" + "summary": "Added the 'theVar' identifier" } ] }, @@ -74,9 +71,9 @@ "filePaths": [ "identifier.js" ], - "sha1": "820fa9e9590b2599eceae072c5f58cdbdb9a537c", + "sha1": "7c6643be086c41a5cd376fbf7b36e2f7d33bc1bf", "gitDir": "test/corpus/repos/javascript", - "sha2": "2d5f6d80071c263cbc273856778d3251ce74517f" + "sha2": "9714f432aec25fb2318e2dab9f9b2a78fc5cb22f" } ,{ "testCaseDescription": "javascript-identifier-delete-insert-test", @@ -108,8 +105,7 @@ } ] }, - "summary": "Replaced the 'theVar2' identifier with the 'theVar' identifier", - "tag": "JSONSummary" + "summary": "Replaced the 'theVar2' identifier with the 'theVar' identifier" } ] }, @@ -118,9 +114,9 @@ "filePaths": [ "identifier.js" ], - "sha1": "2d5f6d80071c263cbc273856778d3251ce74517f", + "sha1": "9714f432aec25fb2318e2dab9f9b2a78fc5cb22f", "gitDir": "test/corpus/repos/javascript", - "sha2": "3f31f4a9c07a65eb2798133713f2f34fcee799c8" + "sha2": "93fd36c156a2e1bd23e2e5777f4b5b7e7a82c7cb" } ,{ "testCaseDescription": "javascript-identifier-replacement-test", @@ -152,8 +148,7 @@ } ] }, - "summary": "Replaced the 'theVar' identifier with the 'theVar2' identifier", - "tag": "JSONSummary" + "summary": "Replaced the 'theVar' identifier with the 'theVar2' identifier" } ] }, @@ -162,9 +157,9 @@ "filePaths": [ "identifier.js" ], - "sha1": "3f31f4a9c07a65eb2798133713f2f34fcee799c8", + "sha1": "93fd36c156a2e1bd23e2e5777f4b5b7e7a82c7cb", "gitDir": "test/corpus/repos/javascript", - "sha2": "fd58b769ec4b48c0bee68cfe834c8bb1adcdb516" + "sha2": "cfb79cbb2bcd620edb55c909983e5e631a08c863" } ,{ "testCaseDescription": "javascript-identifier-delete-replacement-test", @@ -184,8 +179,7 @@ ] } }, - "summary": "Deleted the 'theVar2' identifier", - "tag": "JSONSummary" + "summary": "Deleted the 'theVar2' identifier" }, { "span": { @@ -200,8 +194,7 @@ ] } }, - "summary": "Deleted the 'theVar' identifier", - "tag": "JSONSummary" + "summary": "Deleted the 'theVar' identifier" }, { "span": { @@ -216,8 +209,7 @@ ] } }, - "summary": "Added the 'theVar2' identifier", - "tag": "JSONSummary" + "summary": "Added the 'theVar2' identifier" } ] }, @@ -226,9 +218,9 @@ "filePaths": [ "identifier.js" ], - "sha1": "fd58b769ec4b48c0bee68cfe834c8bb1adcdb516", + "sha1": "cfb79cbb2bcd620edb55c909983e5e631a08c863", "gitDir": "test/corpus/repos/javascript", - "sha2": "2a566f75e47f4106c9d875d7090b32ba869ed332" + "sha2": "106dff12bfb07dc175748db3ce6f8a6ace4a561a" } ,{ "testCaseDescription": "javascript-identifier-delete-test", @@ -248,8 +240,7 @@ ] } }, - "summary": "Deleted the 'theVar' identifier", - "tag": "JSONSummary" + "summary": "Deleted the 'theVar' identifier" } ] }, @@ -258,9 +249,9 @@ "filePaths": [ "identifier.js" ], - "sha1": "2a566f75e47f4106c9d875d7090b32ba869ed332", + "sha1": "106dff12bfb07dc175748db3ce6f8a6ace4a561a", "gitDir": "test/corpus/repos/javascript", - "sha2": "ebe92c64b9f8a0a4b422493d741cff603d82974b" + "sha2": "947a90cdedee234b01c85052f7bb112fb1e7eae0" } ,{ "testCaseDescription": "javascript-identifier-delete-rest-test", @@ -280,8 +271,7 @@ ] } }, - "summary": "Deleted the 'theVar2' identifier", - "tag": "JSONSummary" + "summary": "Deleted the 'theVar2' identifier" } ] }, @@ -290,7 +280,7 @@ "filePaths": [ "identifier.js" ], - "sha1": "ebe92c64b9f8a0a4b422493d741cff603d82974b", + "sha1": "947a90cdedee234b01c85052f7bb112fb1e7eae0", "gitDir": "test/corpus/repos/javascript", - "sha2": "35dca27c6725f2defede78609517066c5e1b30dc" + "sha2": "d7c66b2feea9aa25c92f9e3005737bcd96679136" }] diff --git a/test/corpus/diff-summaries/javascript/if-else.json b/test/corpus/diff-summaries/javascript/if-else.json index 66f27ec0d..fa28d3b31 100644 --- a/test/corpus/diff-summaries/javascript/if-else.json +++ b/test/corpus/diff-summaries/javascript/if-else.json @@ -16,8 +16,7 @@ ] } }, - "summary": "Added the 'x' if statement", - "tag": "JSONSummary" + "summary": "Added the 'x' if statement" } ] }, @@ -26,9 +25,9 @@ "filePaths": [ "if-else.js" ], - "sha1": "9791d662a9cbd0fe8d9219fcf7550a3417954956", + "sha1": "177b3db7ca070dc750876553a0cd7fde8b5df54c", "gitDir": "test/corpus/repos/javascript", - "sha2": "7af553e3a57c0d33f2c020598c2f05db9398f594" + "sha2": "fd499e58d749df1da475f0d6033825f265734210" } ,{ "testCaseDescription": "javascript-if-else-replacement-insert-test", @@ -48,8 +47,7 @@ ] } }, - "summary": "Added the 'a' if statement", - "tag": "JSONSummary" + "summary": "Added the 'a' if statement" }, { "span": { @@ -64,8 +62,7 @@ ] } }, - "summary": "Added the 'x' if statement", - "tag": "JSONSummary" + "summary": "Added the 'x' if statement" } ] }, @@ -74,9 +71,9 @@ "filePaths": [ "if-else.js" ], - "sha1": "7af553e3a57c0d33f2c020598c2f05db9398f594", + "sha1": "fd499e58d749df1da475f0d6033825f265734210", "gitDir": "test/corpus/repos/javascript", - "sha2": "651c15bb59c428793be04e7072f6d137832df250" + "sha2": "1f6c19a2b78ca415ac6e06f69c051ba6c23a250e" } ,{ "testCaseDescription": "javascript-if-else-delete-insert-test", @@ -108,8 +105,7 @@ } ] }, - "summary": "Replaced the 'a' if statement with the 'x' if statement", - "tag": "JSONSummary" + "summary": "Replaced the 'a' if statement with the 'x' if statement" } ] }, @@ -118,9 +114,9 @@ "filePaths": [ "if-else.js" ], - "sha1": "651c15bb59c428793be04e7072f6d137832df250", + "sha1": "1f6c19a2b78ca415ac6e06f69c051ba6c23a250e", "gitDir": "test/corpus/repos/javascript", - "sha2": "15b975c4d4e28f674c65de1da47ba66daafc29bf" + "sha2": "946c2d3269de0a2f284a9922b8da111323729827" } ,{ "testCaseDescription": "javascript-if-else-replacement-test", @@ -152,8 +148,7 @@ } ] }, - "summary": "Replaced the 'x' if statement with the 'a' if statement", - "tag": "JSONSummary" + "summary": "Replaced the 'x' if statement with the 'a' if statement" } ] }, @@ -162,9 +157,9 @@ "filePaths": [ "if-else.js" ], - "sha1": "15b975c4d4e28f674c65de1da47ba66daafc29bf", + "sha1": "946c2d3269de0a2f284a9922b8da111323729827", "gitDir": "test/corpus/repos/javascript", - "sha2": "2ee5946e894b4aa6269be6efb6f47f568208cbba" + "sha2": "71792b4ff0291e41c9e3ec3157abfea9cd67daa7" } ,{ "testCaseDescription": "javascript-if-else-delete-replacement-test", @@ -184,8 +179,7 @@ ] } }, - "summary": "Deleted the 'a' if statement", - "tag": "JSONSummary" + "summary": "Deleted the 'a' if statement" }, { "span": { @@ -200,8 +194,7 @@ ] } }, - "summary": "Deleted the 'x' if statement", - "tag": "JSONSummary" + "summary": "Deleted the 'x' if statement" }, { "span": { @@ -216,8 +209,7 @@ ] } }, - "summary": "Added the 'a' if statement", - "tag": "JSONSummary" + "summary": "Added the 'a' if statement" } ] }, @@ -226,9 +218,9 @@ "filePaths": [ "if-else.js" ], - "sha1": "2ee5946e894b4aa6269be6efb6f47f568208cbba", + "sha1": "71792b4ff0291e41c9e3ec3157abfea9cd67daa7", "gitDir": "test/corpus/repos/javascript", - "sha2": "afba47fff506da21a377692c35e52c9777ffa56b" + "sha2": "95edd1d597a111bbe508c047a0f75d0342b35cea" } ,{ "testCaseDescription": "javascript-if-else-delete-test", @@ -248,8 +240,7 @@ ] } }, - "summary": "Deleted the 'x' if statement", - "tag": "JSONSummary" + "summary": "Deleted the 'x' if statement" } ] }, @@ -258,9 +249,9 @@ "filePaths": [ "if-else.js" ], - "sha1": "afba47fff506da21a377692c35e52c9777ffa56b", + "sha1": "95edd1d597a111bbe508c047a0f75d0342b35cea", "gitDir": "test/corpus/repos/javascript", - "sha2": "b8cf4deac8a619ffabbbb6619640509d2a12f6af" + "sha2": "58fd81ed8b29ab258997ccdcb2a0602e64748fc8" } ,{ "testCaseDescription": "javascript-if-else-delete-rest-test", @@ -280,8 +271,7 @@ ] } }, - "summary": "Deleted the 'a' if statement", - "tag": "JSONSummary" + "summary": "Deleted the 'a' if statement" } ] }, @@ -290,7 +280,7 @@ "filePaths": [ "if-else.js" ], - "sha1": "b8cf4deac8a619ffabbbb6619640509d2a12f6af", + "sha1": "58fd81ed8b29ab258997ccdcb2a0602e64748fc8", "gitDir": "test/corpus/repos/javascript", - "sha2": "2d5d9ee14704ef70452e42e144662eceacdb562d" + "sha2": "73e8a48299a8c408fadbf83077ab1e56ea81b5b0" }] diff --git a/test/corpus/diff-summaries/javascript/if.json b/test/corpus/diff-summaries/javascript/if.json index 860ad92b4..ace3329dc 100644 --- a/test/corpus/diff-summaries/javascript/if.json +++ b/test/corpus/diff-summaries/javascript/if.json @@ -16,8 +16,7 @@ ] } }, - "summary": "Added the 'x' if statement", - "tag": "JSONSummary" + "summary": "Added the 'x' if statement" } ] }, @@ -26,9 +25,9 @@ "filePaths": [ "if.js" ], - "sha1": "019ed2c1f543531ab1678c9fcd7dd223ad5ca8b2", + "sha1": "12025ea457b9f71f1c34d8354dcfef593fccd770", "gitDir": "test/corpus/repos/javascript", - "sha2": "a4b4113212a03138f0546396dfb35170538bb846" + "sha2": "be1ba1d9246e11b23be78baf2717476ab716b9bf" } ,{ "testCaseDescription": "javascript-if-replacement-insert-test", @@ -48,8 +47,7 @@ ] } }, - "summary": "Added the 'a.b' if statement", - "tag": "JSONSummary" + "summary": "Added the 'a.b' if statement" }, { "span": { @@ -64,8 +62,7 @@ ] } }, - "summary": "Added the 'x' if statement", - "tag": "JSONSummary" + "summary": "Added the 'x' if statement" } ] }, @@ -74,9 +71,9 @@ "filePaths": [ "if.js" ], - "sha1": "a4b4113212a03138f0546396dfb35170538bb846", + "sha1": "be1ba1d9246e11b23be78baf2717476ab716b9bf", "gitDir": "test/corpus/repos/javascript", - "sha2": "874a29b843b633497b98f99ab606daa42e02402f" + "sha2": "c01e982383545a2a238b3a6af70f2c1268e473d6" } ,{ "testCaseDescription": "javascript-if-delete-insert-test", @@ -108,8 +105,7 @@ } ] }, - "summary": "Replaced the 'a.b' if statement with the 'x' if statement", - "tag": "JSONSummary" + "summary": "Replaced the 'a.b' if statement with the 'x' if statement" } ] }, @@ -118,9 +114,9 @@ "filePaths": [ "if.js" ], - "sha1": "874a29b843b633497b98f99ab606daa42e02402f", + "sha1": "c01e982383545a2a238b3a6af70f2c1268e473d6", "gitDir": "test/corpus/repos/javascript", - "sha2": "16128f22ec566f5acbb690d0ef838d6227cdd402" + "sha2": "6040b05311f729269cebedf1d54c8038788faf89" } ,{ "testCaseDescription": "javascript-if-replacement-test", @@ -152,8 +148,7 @@ } ] }, - "summary": "Replaced the 'x' if statement with the 'a.b' if statement", - "tag": "JSONSummary" + "summary": "Replaced the 'x' if statement with the 'a.b' if statement" } ] }, @@ -162,9 +157,9 @@ "filePaths": [ "if.js" ], - "sha1": "16128f22ec566f5acbb690d0ef838d6227cdd402", + "sha1": "6040b05311f729269cebedf1d54c8038788faf89", "gitDir": "test/corpus/repos/javascript", - "sha2": "9fd01fbbfa583c431e65fa74fb11ab8bfce478a5" + "sha2": "ea9839117fdd5a20b5a49fd5bec5b0edf373e914" } ,{ "testCaseDescription": "javascript-if-delete-replacement-test", @@ -184,8 +179,7 @@ ] } }, - "summary": "Deleted the 'a.b' if statement", - "tag": "JSONSummary" + "summary": "Deleted the 'a.b' if statement" }, { "span": { @@ -200,8 +194,7 @@ ] } }, - "summary": "Deleted the 'x' if statement", - "tag": "JSONSummary" + "summary": "Deleted the 'x' if statement" }, { "span": { @@ -216,8 +209,7 @@ ] } }, - "summary": "Added the 'a.b' if statement", - "tag": "JSONSummary" + "summary": "Added the 'a.b' if statement" } ] }, @@ -226,9 +218,9 @@ "filePaths": [ "if.js" ], - "sha1": "9fd01fbbfa583c431e65fa74fb11ab8bfce478a5", + "sha1": "ea9839117fdd5a20b5a49fd5bec5b0edf373e914", "gitDir": "test/corpus/repos/javascript", - "sha2": "e7e84a047077fb4d105e58efd5866b2ac0a4d12a" + "sha2": "450d9d28a46d3283979a55c31dcf4cd7fadd979b" } ,{ "testCaseDescription": "javascript-if-delete-test", @@ -248,8 +240,7 @@ ] } }, - "summary": "Deleted the 'x' if statement", - "tag": "JSONSummary" + "summary": "Deleted the 'x' if statement" } ] }, @@ -258,9 +249,9 @@ "filePaths": [ "if.js" ], - "sha1": "e7e84a047077fb4d105e58efd5866b2ac0a4d12a", + "sha1": "450d9d28a46d3283979a55c31dcf4cd7fadd979b", "gitDir": "test/corpus/repos/javascript", - "sha2": "c026ca9c14269cbdaa6e276375c1e6a635e93067" + "sha2": "d96611306db475c3b49c4e6f7c2ac07fedee9c42" } ,{ "testCaseDescription": "javascript-if-delete-rest-test", @@ -280,8 +271,7 @@ ] } }, - "summary": "Deleted the 'a.b' if statement", - "tag": "JSONSummary" + "summary": "Deleted the 'a.b' if statement" } ] }, @@ -290,7 +280,7 @@ "filePaths": [ "if.js" ], - "sha1": "c026ca9c14269cbdaa6e276375c1e6a635e93067", + "sha1": "d96611306db475c3b49c4e6f7c2ac07fedee9c42", "gitDir": "test/corpus/repos/javascript", - "sha2": "cb6ecdcdc2f19afb8b09b417b7b3789de92bbe2c" + "sha2": "0e12557e9a116aa82c320e964f67655fe82a8476" }] diff --git a/test/corpus/diff-summaries/javascript/import.json b/test/corpus/diff-summaries/javascript/import.json index 28e46ab35..263d2f44f 100644 --- a/test/corpus/diff-summaries/javascript/import.json +++ b/test/corpus/diff-summaries/javascript/import.json @@ -16,8 +16,7 @@ ] } }, - "summary": "Added the '\"foo\"' import statement", - "tag": "JSONSummary" + "summary": "Added the '\"foo\"' import statement" }, { "span": { @@ -32,8 +31,7 @@ ] } }, - "summary": "Added the '\"aardvark\"' import statement", - "tag": "JSONSummary" + "summary": "Added the '\"aardvark\"' import statement" }, { "span": { @@ -48,8 +46,7 @@ ] } }, - "summary": "Added the '\"ant\"' import statement", - "tag": "JSONSummary" + "summary": "Added the '\"ant\"' import statement" }, { "span": { @@ -64,8 +61,7 @@ ] } }, - "summary": "Added the '\"antelope\"' import statement", - "tag": "JSONSummary" + "summary": "Added the '\"antelope\"' import statement" }, { "span": { @@ -80,8 +76,7 @@ ] } }, - "summary": "Added the '\"ant-eater\"' import statement", - "tag": "JSONSummary" + "summary": "Added the '\"ant-eater\"' import statement" }, { "span": { @@ -96,8 +91,7 @@ ] } }, - "summary": "Added the '\"anaconda\"' import statement", - "tag": "JSONSummary" + "summary": "Added the '\"anaconda\"' import statement" }, { "span": { @@ -112,8 +106,7 @@ ] } }, - "summary": "Added the '\"alligator\"' import statement", - "tag": "JSONSummary" + "summary": "Added the '\"alligator\"' import statement" }, { "span": { @@ -128,8 +121,7 @@ ] } }, - "summary": "Added the '\"arctic-tern\"' import statement", - "tag": "JSONSummary" + "summary": "Added the '\"arctic-tern\"' import statement" } ] }, @@ -138,9 +130,9 @@ "filePaths": [ "import.js" ], - "sha1": "79e42f5e2d2b5990e809542916065fbb29e4ec4d", + "sha1": "969de35a1ab58e78a2a3d5cead43f25486fa0969", "gitDir": "test/corpus/repos/javascript", - "sha2": "fee3454c33f7cd5eab32dc5aa7e9735a955ace4f" + "sha2": "e4961fa1bc48e9aa157a172e22fca0b5daa58610" } ,{ "testCaseDescription": "javascript-import-replacement-insert-test", @@ -160,8 +152,7 @@ ] } }, - "summary": "Added the '\"babirusa\"' import statement", - "tag": "JSONSummary" + "summary": "Added the '\"babirusa\"' import statement" }, { "span": { @@ -176,8 +167,7 @@ ] } }, - "summary": "Added the '\"baboon\"' import statement", - "tag": "JSONSummary" + "summary": "Added the '\"baboon\"' import statement" }, { "span": { @@ -192,8 +182,7 @@ ] } }, - "summary": "Added the '\"badger\"' import statement", - "tag": "JSONSummary" + "summary": "Added the '\"badger\"' import statement" }, { "span": { @@ -208,8 +197,7 @@ ] } }, - "summary": "Added the '\"bald-eagle\"' import statement", - "tag": "JSONSummary" + "summary": "Added the '\"bald-eagle\"' import statement" }, { "span": { @@ -224,8 +212,7 @@ ] } }, - "summary": "Added the '\"bandicoot\"' import statement", - "tag": "JSONSummary" + "summary": "Added the '\"bandicoot\"' import statement" }, { "span": { @@ -240,8 +227,7 @@ ] } }, - "summary": "Added the '\"banteng\"' import statement", - "tag": "JSONSummary" + "summary": "Added the '\"banteng\"' import statement" }, { "span": { @@ -256,8 +242,7 @@ ] } }, - "summary": "Added the '\"barbet\"' import statement", - "tag": "JSONSummary" + "summary": "Added the '\"barbet\"' import statement" }, { "span": { @@ -272,8 +257,7 @@ ] } }, - "summary": "Added the '\"basilisk\"' import statement", - "tag": "JSONSummary" + "summary": "Added the '\"basilisk\"' import statement" }, { "span": { @@ -288,8 +272,7 @@ ] } }, - "summary": "Added the '\"foo\"' import statement", - "tag": "JSONSummary" + "summary": "Added the '\"foo\"' import statement" }, { "span": { @@ -304,8 +287,7 @@ ] } }, - "summary": "Added the '\"aardvark\"' import statement", - "tag": "JSONSummary" + "summary": "Added the '\"aardvark\"' import statement" }, { "span": { @@ -320,8 +302,7 @@ ] } }, - "summary": "Added the '\"ant\"' import statement", - "tag": "JSONSummary" + "summary": "Added the '\"ant\"' import statement" }, { "span": { @@ -336,8 +317,7 @@ ] } }, - "summary": "Added the '\"antelope\"' import statement", - "tag": "JSONSummary" + "summary": "Added the '\"antelope\"' import statement" }, { "span": { @@ -352,8 +332,7 @@ ] } }, - "summary": "Added the '\"ant-eater\"' import statement", - "tag": "JSONSummary" + "summary": "Added the '\"ant-eater\"' import statement" }, { "span": { @@ -368,8 +347,7 @@ ] } }, - "summary": "Added the '\"anaconda\"' import statement", - "tag": "JSONSummary" + "summary": "Added the '\"anaconda\"' import statement" }, { "span": { @@ -384,8 +362,7 @@ ] } }, - "summary": "Added the '\"alligator\"' import statement", - "tag": "JSONSummary" + "summary": "Added the '\"alligator\"' import statement" }, { "span": { @@ -400,8 +377,7 @@ ] } }, - "summary": "Added the '\"arctic-tern\"' import statement", - "tag": "JSONSummary" + "summary": "Added the '\"arctic-tern\"' import statement" } ] }, @@ -410,9 +386,9 @@ "filePaths": [ "import.js" ], - "sha1": "fee3454c33f7cd5eab32dc5aa7e9735a955ace4f", + "sha1": "e4961fa1bc48e9aa157a172e22fca0b5daa58610", "gitDir": "test/corpus/repos/javascript", - "sha2": "c28f080d1c93051935cf781db3adc4d790fdd8ed" + "sha2": "79337911d1d279db1c8f7e5c804ae138a9828ad6" } ,{ "testCaseDescription": "javascript-import-delete-insert-test", @@ -444,8 +420,7 @@ } ] }, - "summary": "Replaced the \"babirusa\" string with the \"foo\" string in the \"foo\" import statement", - "tag": "JSONSummary" + "summary": "Replaced the \"babirusa\" string with the \"foo\" string in the \"foo\" import statement" }, { "span": { @@ -472,8 +447,7 @@ } ] }, - "summary": "Replaced the \"baboon\" string with the \"aardvark\" string in the \"aardvark\" import statement", - "tag": "JSONSummary" + "summary": "Replaced the \"baboon\" string with the \"aardvark\" string in the \"aardvark\" import statement" }, { "span": { @@ -500,8 +474,7 @@ } ] }, - "summary": "Replaced the 'otherName' identifier with the 'name' identifier in the \"aardvark\" import statement", - "tag": "JSONSummary" + "summary": "Replaced the 'otherName' identifier with the 'name' identifier in the \"aardvark\" import statement" }, { "span": { @@ -528,8 +501,7 @@ } ] }, - "summary": "Replaced the \"badger\" string with the \"ant\" string in the \"ant\" import statement", - "tag": "JSONSummary" + "summary": "Replaced the \"badger\" string with the \"ant\" string in the \"ant\" import statement" }, { "span": { @@ -556,8 +528,7 @@ } ] }, - "summary": "Replaced the 'element' identifier with the 'member' identifier in the \"ant\" import statement", - "tag": "JSONSummary" + "summary": "Replaced the 'element' identifier with the 'member' identifier in the \"ant\" import statement" }, { "span": { @@ -584,8 +555,7 @@ } ] }, - "summary": "Replaced the \"bald-eagle\" string with the \"antelope\" string in the \"antelope\" import statement", - "tag": "JSONSummary" + "summary": "Replaced the \"bald-eagle\" string with the \"antelope\" string in the \"antelope\" import statement" }, { "span": { @@ -612,8 +582,7 @@ } ] }, - "summary": "Replaced the 'element1' identifier with the 'member1' identifier in the \"antelope\" import statement", - "tag": "JSONSummary" + "summary": "Replaced the 'element1' identifier with the 'member1' identifier in the \"antelope\" import statement" }, { "span": { @@ -640,8 +609,7 @@ } ] }, - "summary": "Replaced the 'element2' identifier with the 'member2' identifier in the \"antelope\" import statement", - "tag": "JSONSummary" + "summary": "Replaced the 'element2' identifier with the 'member2' identifier in the \"antelope\" import statement" }, { "span": { @@ -668,8 +636,7 @@ } ] }, - "summary": "Replaced the \"bandicoot\" string with the \"ant-eater\" string in the \"ant-eater\" import statement", - "tag": "JSONSummary" + "summary": "Replaced the \"bandicoot\" string with the \"ant-eater\" string in the \"ant-eater\" import statement" }, { "span": { @@ -696,8 +663,7 @@ } ] }, - "summary": "Replaced the 'element1' identifier with the 'member1' identifier in the \"ant-eater\" import statement", - "tag": "JSONSummary" + "summary": "Replaced the 'element1' identifier with the 'member1' identifier in the \"ant-eater\" import statement" }, { "span": { @@ -724,8 +690,7 @@ } ] }, - "summary": "Replaced the 'element2' identifier with the 'member2' identifier in the \"ant-eater\" import statement", - "tag": "JSONSummary" + "summary": "Replaced the 'element2' identifier with the 'member2' identifier in the \"ant-eater\" import statement" }, { "span": { @@ -752,8 +717,7 @@ } ] }, - "summary": "Replaced the 'elementAlias2' identifier with the 'alias2' identifier in the \"ant-eater\" import statement", - "tag": "JSONSummary" + "summary": "Replaced the 'elementAlias2' identifier with the 'alias2' identifier in the \"ant-eater\" import statement" }, { "span": { @@ -780,8 +744,7 @@ } ] }, - "summary": "Replaced the \"banteng\" string with the \"anaconda\" string in the \"anaconda\" import statement", - "tag": "JSONSummary" + "summary": "Replaced the \"banteng\" string with the \"anaconda\" string in the \"anaconda\" import statement" }, { "span": { @@ -808,8 +771,7 @@ } ] }, - "summary": "Replaced the 'element1' identifier with the 'member1' identifier in the \"anaconda\" import statement", - "tag": "JSONSummary" + "summary": "Replaced the 'element1' identifier with the 'member1' identifier in the \"anaconda\" import statement" }, { "span": { @@ -836,8 +798,7 @@ } ] }, - "summary": "Replaced the 'element2' identifier with the 'member2' identifier in the \"anaconda\" import statement", - "tag": "JSONSummary" + "summary": "Replaced the 'element2' identifier with the 'member2' identifier in the \"anaconda\" import statement" }, { "span": { @@ -864,8 +825,7 @@ } ] }, - "summary": "Replaced the 'elementAlias2' identifier with the 'alias2' identifier in the \"anaconda\" import statement", - "tag": "JSONSummary" + "summary": "Replaced the 'elementAlias2' identifier with the 'alias2' identifier in the \"anaconda\" import statement" }, { "span": { @@ -892,8 +852,7 @@ } ] }, - "summary": "Replaced the \"barbet\" string with the \"alligator\" string in the \"alligator\" import statement", - "tag": "JSONSummary" + "summary": "Replaced the \"barbet\" string with the \"alligator\" string in the \"alligator\" import statement" }, { "span": { @@ -920,8 +879,7 @@ } ] }, - "summary": "Replaced the 'element' identifier with the 'name' identifier in the \"alligator\" import statement", - "tag": "JSONSummary" + "summary": "Replaced the 'element' identifier with the 'name' identifier in the \"alligator\" import statement" }, { "span": { @@ -948,8 +906,7 @@ } ] }, - "summary": "Replaced the \"basilisk\" string with the \"arctic-tern\" string in the \"arctic-tern\" import statement", - "tag": "JSONSummary" + "summary": "Replaced the \"basilisk\" string with the \"arctic-tern\" string in the \"arctic-tern\" import statement" } ] }, @@ -958,9 +915,9 @@ "filePaths": [ "import.js" ], - "sha1": "c28f080d1c93051935cf781db3adc4d790fdd8ed", + "sha1": "79337911d1d279db1c8f7e5c804ae138a9828ad6", "gitDir": "test/corpus/repos/javascript", - "sha2": "26fd9db0c145d7d502593173826c0f1ad31dc8d6" + "sha2": "8d4527bce8c95528790ff0069721625d57d52453" } ,{ "testCaseDescription": "javascript-import-replacement-test", @@ -992,8 +949,7 @@ } ] }, - "summary": "Replaced the \"foo\" string with the \"babirusa\" string in the \"babirusa\" import statement", - "tag": "JSONSummary" + "summary": "Replaced the \"foo\" string with the \"babirusa\" string in the \"babirusa\" import statement" }, { "span": { @@ -1020,8 +976,7 @@ } ] }, - "summary": "Replaced the \"aardvark\" string with the \"baboon\" string in the \"baboon\" import statement", - "tag": "JSONSummary" + "summary": "Replaced the \"aardvark\" string with the \"baboon\" string in the \"baboon\" import statement" }, { "span": { @@ -1048,8 +1003,7 @@ } ] }, - "summary": "Replaced the 'name' identifier with the 'otherName' identifier in the \"baboon\" import statement", - "tag": "JSONSummary" + "summary": "Replaced the 'name' identifier with the 'otherName' identifier in the \"baboon\" import statement" }, { "span": { @@ -1076,8 +1030,7 @@ } ] }, - "summary": "Replaced the \"ant\" string with the \"badger\" string in the \"badger\" import statement", - "tag": "JSONSummary" + "summary": "Replaced the \"ant\" string with the \"badger\" string in the \"badger\" import statement" }, { "span": { @@ -1104,8 +1057,7 @@ } ] }, - "summary": "Replaced the 'member' identifier with the 'element' identifier in the \"badger\" import statement", - "tag": "JSONSummary" + "summary": "Replaced the 'member' identifier with the 'element' identifier in the \"badger\" import statement" }, { "span": { @@ -1132,8 +1084,7 @@ } ] }, - "summary": "Replaced the \"antelope\" string with the \"bald-eagle\" string in the \"bald-eagle\" import statement", - "tag": "JSONSummary" + "summary": "Replaced the \"antelope\" string with the \"bald-eagle\" string in the \"bald-eagle\" import statement" }, { "span": { @@ -1160,8 +1111,7 @@ } ] }, - "summary": "Replaced the 'member1' identifier with the 'element1' identifier in the \"bald-eagle\" import statement", - "tag": "JSONSummary" + "summary": "Replaced the 'member1' identifier with the 'element1' identifier in the \"bald-eagle\" import statement" }, { "span": { @@ -1188,8 +1138,7 @@ } ] }, - "summary": "Replaced the 'member2' identifier with the 'element2' identifier in the \"bald-eagle\" import statement", - "tag": "JSONSummary" + "summary": "Replaced the 'member2' identifier with the 'element2' identifier in the \"bald-eagle\" import statement" }, { "span": { @@ -1216,8 +1165,7 @@ } ] }, - "summary": "Replaced the \"ant-eater\" string with the \"bandicoot\" string in the \"bandicoot\" import statement", - "tag": "JSONSummary" + "summary": "Replaced the \"ant-eater\" string with the \"bandicoot\" string in the \"bandicoot\" import statement" }, { "span": { @@ -1244,8 +1192,7 @@ } ] }, - "summary": "Replaced the 'member1' identifier with the 'element1' identifier in the \"bandicoot\" import statement", - "tag": "JSONSummary" + "summary": "Replaced the 'member1' identifier with the 'element1' identifier in the \"bandicoot\" import statement" }, { "span": { @@ -1272,8 +1219,7 @@ } ] }, - "summary": "Replaced the 'member2' identifier with the 'element2' identifier in the \"bandicoot\" import statement", - "tag": "JSONSummary" + "summary": "Replaced the 'member2' identifier with the 'element2' identifier in the \"bandicoot\" import statement" }, { "span": { @@ -1300,8 +1246,7 @@ } ] }, - "summary": "Replaced the 'alias2' identifier with the 'elementAlias2' identifier in the \"bandicoot\" import statement", - "tag": "JSONSummary" + "summary": "Replaced the 'alias2' identifier with the 'elementAlias2' identifier in the \"bandicoot\" import statement" }, { "span": { @@ -1328,8 +1273,7 @@ } ] }, - "summary": "Replaced the \"anaconda\" string with the \"banteng\" string in the \"banteng\" import statement", - "tag": "JSONSummary" + "summary": "Replaced the \"anaconda\" string with the \"banteng\" string in the \"banteng\" import statement" }, { "span": { @@ -1356,8 +1300,7 @@ } ] }, - "summary": "Replaced the 'member1' identifier with the 'element1' identifier in the \"banteng\" import statement", - "tag": "JSONSummary" + "summary": "Replaced the 'member1' identifier with the 'element1' identifier in the \"banteng\" import statement" }, { "span": { @@ -1384,8 +1327,7 @@ } ] }, - "summary": "Replaced the 'member2' identifier with the 'element2' identifier in the \"banteng\" import statement", - "tag": "JSONSummary" + "summary": "Replaced the 'member2' identifier with the 'element2' identifier in the \"banteng\" import statement" }, { "span": { @@ -1412,8 +1354,7 @@ } ] }, - "summary": "Replaced the 'alias2' identifier with the 'elementAlias2' identifier in the \"banteng\" import statement", - "tag": "JSONSummary" + "summary": "Replaced the 'alias2' identifier with the 'elementAlias2' identifier in the \"banteng\" import statement" }, { "span": { @@ -1440,8 +1381,7 @@ } ] }, - "summary": "Replaced the \"alligator\" string with the \"barbet\" string in the \"barbet\" import statement", - "tag": "JSONSummary" + "summary": "Replaced the \"alligator\" string with the \"barbet\" string in the \"barbet\" import statement" }, { "span": { @@ -1468,8 +1408,7 @@ } ] }, - "summary": "Replaced the 'name' identifier with the 'element' identifier in the \"barbet\" import statement", - "tag": "JSONSummary" + "summary": "Replaced the 'name' identifier with the 'element' identifier in the \"barbet\" import statement" }, { "span": { @@ -1496,8 +1435,7 @@ } ] }, - "summary": "Replaced the \"arctic-tern\" string with the \"basilisk\" string in the \"basilisk\" import statement", - "tag": "JSONSummary" + "summary": "Replaced the \"arctic-tern\" string with the \"basilisk\" string in the \"basilisk\" import statement" } ] }, @@ -1506,9 +1444,9 @@ "filePaths": [ "import.js" ], - "sha1": "26fd9db0c145d7d502593173826c0f1ad31dc8d6", + "sha1": "8d4527bce8c95528790ff0069721625d57d52453", "gitDir": "test/corpus/repos/javascript", - "sha2": "4847728b759c2df8061704204aeb1b24c3d9e5f4" + "sha2": "94fc50c3a96433235f388106a83e12feb3f0dbc5" } ,{ "testCaseDescription": "javascript-import-delete-replacement-test", @@ -1528,8 +1466,7 @@ ] } }, - "summary": "Deleted the '\"babirusa\"' import statement", - "tag": "JSONSummary" + "summary": "Deleted the '\"babirusa\"' import statement" }, { "span": { @@ -1544,8 +1481,7 @@ ] } }, - "summary": "Deleted the '\"baboon\"' import statement", - "tag": "JSONSummary" + "summary": "Deleted the '\"baboon\"' import statement" }, { "span": { @@ -1560,8 +1496,7 @@ ] } }, - "summary": "Deleted the '\"badger\"' import statement", - "tag": "JSONSummary" + "summary": "Deleted the '\"badger\"' import statement" }, { "span": { @@ -1576,8 +1511,7 @@ ] } }, - "summary": "Deleted the '\"bald-eagle\"' import statement", - "tag": "JSONSummary" + "summary": "Deleted the '\"bald-eagle\"' import statement" }, { "span": { @@ -1592,8 +1526,7 @@ ] } }, - "summary": "Deleted the '\"bandicoot\"' import statement", - "tag": "JSONSummary" + "summary": "Deleted the '\"bandicoot\"' import statement" }, { "span": { @@ -1608,8 +1541,7 @@ ] } }, - "summary": "Deleted the '\"banteng\"' import statement", - "tag": "JSONSummary" + "summary": "Deleted the '\"banteng\"' import statement" }, { "span": { @@ -1624,8 +1556,7 @@ ] } }, - "summary": "Deleted the '\"barbet\"' import statement", - "tag": "JSONSummary" + "summary": "Deleted the '\"barbet\"' import statement" }, { "span": { @@ -1640,8 +1571,7 @@ ] } }, - "summary": "Deleted the '\"basilisk\"' import statement", - "tag": "JSONSummary" + "summary": "Deleted the '\"basilisk\"' import statement" }, { "span": { @@ -1656,8 +1586,7 @@ ] } }, - "summary": "Deleted the '\"foo\"' import statement", - "tag": "JSONSummary" + "summary": "Deleted the '\"foo\"' import statement" }, { "span": { @@ -1672,8 +1601,7 @@ ] } }, - "summary": "Deleted the '\"aardvark\"' import statement", - "tag": "JSONSummary" + "summary": "Deleted the '\"aardvark\"' import statement" }, { "span": { @@ -1688,8 +1616,7 @@ ] } }, - "summary": "Deleted the '\"ant\"' import statement", - "tag": "JSONSummary" + "summary": "Deleted the '\"ant\"' import statement" }, { "span": { @@ -1704,8 +1631,7 @@ ] } }, - "summary": "Deleted the '\"antelope\"' import statement", - "tag": "JSONSummary" + "summary": "Deleted the '\"antelope\"' import statement" }, { "span": { @@ -1720,8 +1646,7 @@ ] } }, - "summary": "Deleted the '\"ant-eater\"' import statement", - "tag": "JSONSummary" + "summary": "Deleted the '\"ant-eater\"' import statement" }, { "span": { @@ -1736,8 +1661,7 @@ ] } }, - "summary": "Deleted the '\"anaconda\"' import statement", - "tag": "JSONSummary" + "summary": "Deleted the '\"anaconda\"' import statement" }, { "span": { @@ -1752,8 +1676,7 @@ ] } }, - "summary": "Deleted the '\"alligator\"' import statement", - "tag": "JSONSummary" + "summary": "Deleted the '\"alligator\"' import statement" }, { "span": { @@ -1768,8 +1691,7 @@ ] } }, - "summary": "Deleted the '\"arctic-tern\"' import statement", - "tag": "JSONSummary" + "summary": "Deleted the '\"arctic-tern\"' import statement" }, { "span": { @@ -1784,8 +1706,7 @@ ] } }, - "summary": "Added the '\"babirusa\"' import statement", - "tag": "JSONSummary" + "summary": "Added the '\"babirusa\"' import statement" }, { "span": { @@ -1800,8 +1721,7 @@ ] } }, - "summary": "Added the '\"baboon\"' import statement", - "tag": "JSONSummary" + "summary": "Added the '\"baboon\"' import statement" }, { "span": { @@ -1816,8 +1736,7 @@ ] } }, - "summary": "Added the '\"badger\"' import statement", - "tag": "JSONSummary" + "summary": "Added the '\"badger\"' import statement" }, { "span": { @@ -1832,8 +1751,7 @@ ] } }, - "summary": "Added the '\"bald-eagle\"' import statement", - "tag": "JSONSummary" + "summary": "Added the '\"bald-eagle\"' import statement" }, { "span": { @@ -1848,8 +1766,7 @@ ] } }, - "summary": "Added the '\"bandicoot\"' import statement", - "tag": "JSONSummary" + "summary": "Added the '\"bandicoot\"' import statement" }, { "span": { @@ -1864,8 +1781,7 @@ ] } }, - "summary": "Added the '\"banteng\"' import statement", - "tag": "JSONSummary" + "summary": "Added the '\"banteng\"' import statement" }, { "span": { @@ -1880,8 +1796,7 @@ ] } }, - "summary": "Added the '\"barbet\"' import statement", - "tag": "JSONSummary" + "summary": "Added the '\"barbet\"' import statement" }, { "span": { @@ -1896,8 +1811,7 @@ ] } }, - "summary": "Added the '\"basilisk\"' import statement", - "tag": "JSONSummary" + "summary": "Added the '\"basilisk\"' import statement" } ] }, @@ -1906,9 +1820,9 @@ "filePaths": [ "import.js" ], - "sha1": "4847728b759c2df8061704204aeb1b24c3d9e5f4", + "sha1": "94fc50c3a96433235f388106a83e12feb3f0dbc5", "gitDir": "test/corpus/repos/javascript", - "sha2": "c4905d598dec191b7fd2b15c8d4345ffd7077818" + "sha2": "c6e16f8e22f889194b05370d047adee0492b212a" } ,{ "testCaseDescription": "javascript-import-delete-test", @@ -1928,8 +1842,7 @@ ] } }, - "summary": "Deleted the '\"foo\"' import statement", - "tag": "JSONSummary" + "summary": "Deleted the '\"foo\"' import statement" }, { "span": { @@ -1944,8 +1857,7 @@ ] } }, - "summary": "Deleted the '\"aardvark\"' import statement", - "tag": "JSONSummary" + "summary": "Deleted the '\"aardvark\"' import statement" }, { "span": { @@ -1960,8 +1872,7 @@ ] } }, - "summary": "Deleted the '\"ant\"' import statement", - "tag": "JSONSummary" + "summary": "Deleted the '\"ant\"' import statement" }, { "span": { @@ -1976,8 +1887,7 @@ ] } }, - "summary": "Deleted the '\"antelope\"' import statement", - "tag": "JSONSummary" + "summary": "Deleted the '\"antelope\"' import statement" }, { "span": { @@ -1992,8 +1902,7 @@ ] } }, - "summary": "Deleted the '\"ant-eater\"' import statement", - "tag": "JSONSummary" + "summary": "Deleted the '\"ant-eater\"' import statement" }, { "span": { @@ -2008,8 +1917,7 @@ ] } }, - "summary": "Deleted the '\"anaconda\"' import statement", - "tag": "JSONSummary" + "summary": "Deleted the '\"anaconda\"' import statement" }, { "span": { @@ -2024,8 +1932,7 @@ ] } }, - "summary": "Deleted the '\"alligator\"' import statement", - "tag": "JSONSummary" + "summary": "Deleted the '\"alligator\"' import statement" }, { "span": { @@ -2040,8 +1947,7 @@ ] } }, - "summary": "Deleted the '\"arctic-tern\"' import statement", - "tag": "JSONSummary" + "summary": "Deleted the '\"arctic-tern\"' import statement" } ] }, @@ -2050,9 +1956,9 @@ "filePaths": [ "import.js" ], - "sha1": "c4905d598dec191b7fd2b15c8d4345ffd7077818", + "sha1": "c6e16f8e22f889194b05370d047adee0492b212a", "gitDir": "test/corpus/repos/javascript", - "sha2": "2aefc12e72888e28a1b4fbc7129a1446eb798bc9" + "sha2": "e7da09a2fb206c5b2bbe8c80573730f7c36005a6" } ,{ "testCaseDescription": "javascript-import-delete-rest-test", @@ -2072,8 +1978,7 @@ ] } }, - "summary": "Deleted the '\"babirusa\"' import statement", - "tag": "JSONSummary" + "summary": "Deleted the '\"babirusa\"' import statement" }, { "span": { @@ -2088,8 +1993,7 @@ ] } }, - "summary": "Deleted the '\"baboon\"' import statement", - "tag": "JSONSummary" + "summary": "Deleted the '\"baboon\"' import statement" }, { "span": { @@ -2104,8 +2008,7 @@ ] } }, - "summary": "Deleted the '\"badger\"' import statement", - "tag": "JSONSummary" + "summary": "Deleted the '\"badger\"' import statement" }, { "span": { @@ -2120,8 +2023,7 @@ ] } }, - "summary": "Deleted the '\"bald-eagle\"' import statement", - "tag": "JSONSummary" + "summary": "Deleted the '\"bald-eagle\"' import statement" }, { "span": { @@ -2136,8 +2038,7 @@ ] } }, - "summary": "Deleted the '\"bandicoot\"' import statement", - "tag": "JSONSummary" + "summary": "Deleted the '\"bandicoot\"' import statement" }, { "span": { @@ -2152,8 +2053,7 @@ ] } }, - "summary": "Deleted the '\"banteng\"' import statement", - "tag": "JSONSummary" + "summary": "Deleted the '\"banteng\"' import statement" }, { "span": { @@ -2168,8 +2068,7 @@ ] } }, - "summary": "Deleted the '\"barbet\"' import statement", - "tag": "JSONSummary" + "summary": "Deleted the '\"barbet\"' import statement" }, { "span": { @@ -2184,8 +2083,7 @@ ] } }, - "summary": "Deleted the '\"basilisk\"' import statement", - "tag": "JSONSummary" + "summary": "Deleted the '\"basilisk\"' import statement" } ] }, @@ -2194,7 +2092,7 @@ "filePaths": [ "import.js" ], - "sha1": "2aefc12e72888e28a1b4fbc7129a1446eb798bc9", + "sha1": "e7da09a2fb206c5b2bbe8c80573730f7c36005a6", "gitDir": "test/corpus/repos/javascript", - "sha2": "baeaa709caa4158226fe70b8121ab16a18b17da7" + "sha2": "5fe7b16cba1bd7450b16782afa1d3798fbb6f31c" }] diff --git a/test/corpus/diff-summaries/javascript/math-assignment-operator.json b/test/corpus/diff-summaries/javascript/math-assignment-operator.json index 46b2e1a24..aa8bff563 100644 --- a/test/corpus/diff-summaries/javascript/math-assignment-operator.json +++ b/test/corpus/diff-summaries/javascript/math-assignment-operator.json @@ -16,8 +16,7 @@ ] } }, - "summary": "Added the 'x' math assignment", - "tag": "JSONSummary" + "summary": "Added the 'x' math assignment" } ] }, @@ -26,9 +25,9 @@ "filePaths": [ "math-assignment-operator.js" ], - "sha1": "2ca5d30b5fd1ebde9a1a664d1b82909706d83564", + "sha1": "20c9fcd2968854089edd9800a50d5c4a92d8e07b", "gitDir": "test/corpus/repos/javascript", - "sha2": "c77665677c2dd3b83ba7fefcc63b1d827ffdcce8" + "sha2": "44a0ac752ed04f0db713416a4b71465fcb6791e5" } ,{ "testCaseDescription": "javascript-math-assignment-operator-replacement-insert-test", @@ -48,8 +47,7 @@ ] } }, - "summary": "Added the 'x' math assignment", - "tag": "JSONSummary" + "summary": "Added the 'x' math assignment" }, { "span": { @@ -64,8 +62,7 @@ ] } }, - "summary": "Added the 'x' math assignment", - "tag": "JSONSummary" + "summary": "Added the 'x' math assignment" } ] }, @@ -74,9 +71,9 @@ "filePaths": [ "math-assignment-operator.js" ], - "sha1": "c77665677c2dd3b83ba7fefcc63b1d827ffdcce8", + "sha1": "44a0ac752ed04f0db713416a4b71465fcb6791e5", "gitDir": "test/corpus/repos/javascript", - "sha2": "c2ba4903792d6930abf7ebb660bed06435c39849" + "sha2": "9186895045b5796889b609b6804f3ca92d100c37" } ,{ "testCaseDescription": "javascript-math-assignment-operator-delete-insert-test", @@ -108,8 +105,7 @@ } ] }, - "summary": "Replaced '2' with '1' in the x math assignment", - "tag": "JSONSummary" + "summary": "Replaced '2' with '1' in the x math assignment" } ] }, @@ -118,9 +114,9 @@ "filePaths": [ "math-assignment-operator.js" ], - "sha1": "c2ba4903792d6930abf7ebb660bed06435c39849", + "sha1": "9186895045b5796889b609b6804f3ca92d100c37", "gitDir": "test/corpus/repos/javascript", - "sha2": "c96c70294daa06c57e6f14cb42372b346066a52e" + "sha2": "708ef787fa29646989c2a62e3a38224c6e54150a" } ,{ "testCaseDescription": "javascript-math-assignment-operator-replacement-test", @@ -152,8 +148,7 @@ } ] }, - "summary": "Replaced '1' with '2' in the x math assignment", - "tag": "JSONSummary" + "summary": "Replaced '1' with '2' in the x math assignment" } ] }, @@ -162,9 +157,9 @@ "filePaths": [ "math-assignment-operator.js" ], - "sha1": "c96c70294daa06c57e6f14cb42372b346066a52e", + "sha1": "708ef787fa29646989c2a62e3a38224c6e54150a", "gitDir": "test/corpus/repos/javascript", - "sha2": "4d6fe1c4cb15bf7b1801b95862c70203b5134321" + "sha2": "dba9d03bc3f05c75c64261dc7980015b55215097" } ,{ "testCaseDescription": "javascript-math-assignment-operator-delete-replacement-test", @@ -184,8 +179,7 @@ ] } }, - "summary": "Deleted the 'x' math assignment", - "tag": "JSONSummary" + "summary": "Deleted the 'x' math assignment" }, { "span": { @@ -200,8 +194,7 @@ ] } }, - "summary": "Deleted the 'x' math assignment", - "tag": "JSONSummary" + "summary": "Deleted the 'x' math assignment" }, { "span": { @@ -216,8 +209,7 @@ ] } }, - "summary": "Added the 'x' math assignment", - "tag": "JSONSummary" + "summary": "Added the 'x' math assignment" } ] }, @@ -226,9 +218,9 @@ "filePaths": [ "math-assignment-operator.js" ], - "sha1": "4d6fe1c4cb15bf7b1801b95862c70203b5134321", + "sha1": "dba9d03bc3f05c75c64261dc7980015b55215097", "gitDir": "test/corpus/repos/javascript", - "sha2": "7ac20dbefc8263eb02d522920b8ddb59fdd0b6f3" + "sha2": "4b9bb90264994d44abe5f4178554cbc9364b3fac" } ,{ "testCaseDescription": "javascript-math-assignment-operator-delete-test", @@ -248,8 +240,7 @@ ] } }, - "summary": "Deleted the 'x' math assignment", - "tag": "JSONSummary" + "summary": "Deleted the 'x' math assignment" } ] }, @@ -258,9 +249,9 @@ "filePaths": [ "math-assignment-operator.js" ], - "sha1": "7ac20dbefc8263eb02d522920b8ddb59fdd0b6f3", + "sha1": "4b9bb90264994d44abe5f4178554cbc9364b3fac", "gitDir": "test/corpus/repos/javascript", - "sha2": "8a2ae9688bfc32aab39c26627746cc570e7b65f1" + "sha2": "c6ca546f3e99646514f92e89805309dc8ee3a519" } ,{ "testCaseDescription": "javascript-math-assignment-operator-delete-rest-test", @@ -280,8 +271,7 @@ ] } }, - "summary": "Deleted the 'x' math assignment", - "tag": "JSONSummary" + "summary": "Deleted the 'x' math assignment" } ] }, @@ -290,7 +280,7 @@ "filePaths": [ "math-assignment-operator.js" ], - "sha1": "8a2ae9688bfc32aab39c26627746cc570e7b65f1", + "sha1": "c6ca546f3e99646514f92e89805309dc8ee3a519", "gitDir": "test/corpus/repos/javascript", - "sha2": "4c3640ed0b5a448eb803d90898cfa643a6dd4b71" + "sha2": "296397df0f0e65c6e8ab7e4962469076b890cd66" }] diff --git a/test/corpus/diff-summaries/javascript/math-operator.json b/test/corpus/diff-summaries/javascript/math-operator.json index dc0743394..5aae78353 100644 --- a/test/corpus/diff-summaries/javascript/math-operator.json +++ b/test/corpus/diff-summaries/javascript/math-operator.json @@ -16,8 +16,7 @@ ] } }, - "summary": "Added the 'i + j * 3 - j % 5' math operator", - "tag": "JSONSummary" + "summary": "Added the 'i + j * 3 - j % 5' math operator" } ] }, @@ -26,9 +25,9 @@ "filePaths": [ "math-operator.js" ], - "sha1": "c8a29a317ded4687f422bf074dfc78c3780f2ded", + "sha1": "94851cf65efff14a5d6caad6c5ec3055d75f6891", "gitDir": "test/corpus/repos/javascript", - "sha2": "135b3432e0d4822c6691f908127689ddaf48bd21" + "sha2": "5154551d7bb3028e34b78c57ef6e8251941c5e24" } ,{ "testCaseDescription": "javascript-math-operator-replacement-insert-test", @@ -48,8 +47,7 @@ ] } }, - "summary": "Added the 'i + j * 2 - j % 4' math operator", - "tag": "JSONSummary" + "summary": "Added the 'i + j * 2 - j % 4' math operator" }, { "span": { @@ -64,8 +62,7 @@ ] } }, - "summary": "Added the 'i + j * 3 - j % 5' math operator", - "tag": "JSONSummary" + "summary": "Added the 'i + j * 3 - j % 5' math operator" } ] }, @@ -74,9 +71,9 @@ "filePaths": [ "math-operator.js" ], - "sha1": "135b3432e0d4822c6691f908127689ddaf48bd21", + "sha1": "5154551d7bb3028e34b78c57ef6e8251941c5e24", "gitDir": "test/corpus/repos/javascript", - "sha2": "3bef0fdd5c4f40c4a5842980e32ea9c294e7c1a6" + "sha2": "fc5286a2ab8fbc26558fc824e1673af4c9444af0" } ,{ "testCaseDescription": "javascript-math-operator-delete-insert-test", @@ -108,8 +105,7 @@ } ] }, - "summary": "Replaced '2' with '3'", - "tag": "JSONSummary" + "summary": "Replaced '2' with '3'" }, { "span": { @@ -136,8 +132,7 @@ } ] }, - "summary": "Replaced '4' with '5'", - "tag": "JSONSummary" + "summary": "Replaced '4' with '5'" } ] }, @@ -146,9 +141,9 @@ "filePaths": [ "math-operator.js" ], - "sha1": "3bef0fdd5c4f40c4a5842980e32ea9c294e7c1a6", + "sha1": "fc5286a2ab8fbc26558fc824e1673af4c9444af0", "gitDir": "test/corpus/repos/javascript", - "sha2": "2a1f800e6611e6552c0cc03a075a948be66d821b" + "sha2": "20ff08f05738054ae97a55afe187f062018e7b4a" } ,{ "testCaseDescription": "javascript-math-operator-replacement-test", @@ -180,8 +175,7 @@ } ] }, - "summary": "Replaced '3' with '2'", - "tag": "JSONSummary" + "summary": "Replaced '3' with '2'" }, { "span": { @@ -208,8 +202,7 @@ } ] }, - "summary": "Replaced '5' with '4'", - "tag": "JSONSummary" + "summary": "Replaced '5' with '4'" } ] }, @@ -218,9 +211,9 @@ "filePaths": [ "math-operator.js" ], - "sha1": "2a1f800e6611e6552c0cc03a075a948be66d821b", + "sha1": "20ff08f05738054ae97a55afe187f062018e7b4a", "gitDir": "test/corpus/repos/javascript", - "sha2": "83d548b2ea37b6ff82a5d4934403fcb33b62de2b" + "sha2": "b633411825d8d0d6e48285da3ac8a127bb5b833f" } ,{ "testCaseDescription": "javascript-math-operator-delete-replacement-test", @@ -240,8 +233,7 @@ ] } }, - "summary": "Deleted the 'i + j * 2 - j % 4' math operator", - "tag": "JSONSummary" + "summary": "Deleted the 'i + j * 2 - j % 4' math operator" }, { "span": { @@ -256,8 +248,7 @@ ] } }, - "summary": "Deleted the 'i + j * 3 - j % 5' math operator", - "tag": "JSONSummary" + "summary": "Deleted the 'i + j * 3 - j % 5' math operator" }, { "span": { @@ -272,8 +263,7 @@ ] } }, - "summary": "Added the 'i + j * 2 - j % 4' math operator", - "tag": "JSONSummary" + "summary": "Added the 'i + j * 2 - j % 4' math operator" } ] }, @@ -282,9 +272,9 @@ "filePaths": [ "math-operator.js" ], - "sha1": "83d548b2ea37b6ff82a5d4934403fcb33b62de2b", + "sha1": "b633411825d8d0d6e48285da3ac8a127bb5b833f", "gitDir": "test/corpus/repos/javascript", - "sha2": "ccc69e5cabb4346d9e6e78a680419433965bcaff" + "sha2": "5fba7f8da7725787273fb9fdff3650ee0572bfcd" } ,{ "testCaseDescription": "javascript-math-operator-delete-test", @@ -304,8 +294,7 @@ ] } }, - "summary": "Deleted the 'i + j * 3 - j % 5' math operator", - "tag": "JSONSummary" + "summary": "Deleted the 'i + j * 3 - j % 5' math operator" } ] }, @@ -314,9 +303,9 @@ "filePaths": [ "math-operator.js" ], - "sha1": "ccc69e5cabb4346d9e6e78a680419433965bcaff", + "sha1": "5fba7f8da7725787273fb9fdff3650ee0572bfcd", "gitDir": "test/corpus/repos/javascript", - "sha2": "e12a6e350ec50729b2c8392702dea68bc4f25e19" + "sha2": "971b37d42e25cdfa61a5023a7fbbef5321f2848a" } ,{ "testCaseDescription": "javascript-math-operator-delete-rest-test", @@ -336,8 +325,7 @@ ] } }, - "summary": "Deleted the 'i + j * 2 - j % 4' math operator", - "tag": "JSONSummary" + "summary": "Deleted the 'i + j * 2 - j % 4' math operator" } ] }, @@ -346,7 +334,7 @@ "filePaths": [ "math-operator.js" ], - "sha1": "e12a6e350ec50729b2c8392702dea68bc4f25e19", + "sha1": "971b37d42e25cdfa61a5023a7fbbef5321f2848a", "gitDir": "test/corpus/repos/javascript", - "sha2": "a93c385a37621e58b24c3192ac242f152296869b" + "sha2": "86115e374d32bc9d7b6c8dd347d7ec900b501880" }] diff --git a/test/corpus/diff-summaries/javascript/member-access-assignment.json b/test/corpus/diff-summaries/javascript/member-access-assignment.json index 0f5f56a26..b46603dac 100644 --- a/test/corpus/diff-summaries/javascript/member-access-assignment.json +++ b/test/corpus/diff-summaries/javascript/member-access-assignment.json @@ -16,8 +16,7 @@ ] } }, - "summary": "Added the 'y.x' assignment", - "tag": "JSONSummary" + "summary": "Added the 'y.x' assignment" } ] }, @@ -26,9 +25,9 @@ "filePaths": [ "member-access-assignment.js" ], - "sha1": "fe1724a351896c9096078d5bc7dfa8e89539cddb", + "sha1": "372f806f1ac14eeaef4f8dd5ae1f081823efe483", "gitDir": "test/corpus/repos/javascript", - "sha2": "ac71d5f2e73babcd37c24cb8fade58d08652beae" + "sha2": "a1055cc31a158a5fa654aa40427592b3d6b10c88" } ,{ "testCaseDescription": "javascript-member-access-assignment-replacement-insert-test", @@ -48,8 +47,7 @@ ] } }, - "summary": "Added the 'y.x' assignment", - "tag": "JSONSummary" + "summary": "Added the 'y.x' assignment" }, { "span": { @@ -64,8 +62,7 @@ ] } }, - "summary": "Added the 'y.x' assignment", - "tag": "JSONSummary" + "summary": "Added the 'y.x' assignment" } ] }, @@ -74,9 +71,9 @@ "filePaths": [ "member-access-assignment.js" ], - "sha1": "ac71d5f2e73babcd37c24cb8fade58d08652beae", + "sha1": "a1055cc31a158a5fa654aa40427592b3d6b10c88", "gitDir": "test/corpus/repos/javascript", - "sha2": "45817a82720c40b2e12c4e53e11e3a405e840783" + "sha2": "639b924cdb7df8d54c5accd88915cc8843556868" } ,{ "testCaseDescription": "javascript-member-access-assignment-delete-insert-test", @@ -108,8 +105,7 @@ } ] }, - "summary": "Replaced '1' with '0' in an assignment to y.x", - "tag": "JSONSummary" + "summary": "Replaced '1' with '0' in an assignment to y.x" } ] }, @@ -118,9 +114,9 @@ "filePaths": [ "member-access-assignment.js" ], - "sha1": "45817a82720c40b2e12c4e53e11e3a405e840783", + "sha1": "639b924cdb7df8d54c5accd88915cc8843556868", "gitDir": "test/corpus/repos/javascript", - "sha2": "0b254a3f1120d1cee678a827d0bf5bfb6b57156b" + "sha2": "21f1f660aaa494d71f21feebf996dee749004e74" } ,{ "testCaseDescription": "javascript-member-access-assignment-replacement-test", @@ -152,8 +148,7 @@ } ] }, - "summary": "Replaced '0' with '1' in an assignment to y.x", - "tag": "JSONSummary" + "summary": "Replaced '0' with '1' in an assignment to y.x" } ] }, @@ -162,9 +157,9 @@ "filePaths": [ "member-access-assignment.js" ], - "sha1": "0b254a3f1120d1cee678a827d0bf5bfb6b57156b", + "sha1": "21f1f660aaa494d71f21feebf996dee749004e74", "gitDir": "test/corpus/repos/javascript", - "sha2": "24e43482adbbe8bdbb56191bc3b2ac1387049f77" + "sha2": "62c47a061654573bb752aae3bd9ef9bcceaddf20" } ,{ "testCaseDescription": "javascript-member-access-assignment-delete-replacement-test", @@ -184,8 +179,7 @@ ] } }, - "summary": "Deleted the 'y.x' assignment", - "tag": "JSONSummary" + "summary": "Deleted the 'y.x' assignment" }, { "span": { @@ -200,8 +194,7 @@ ] } }, - "summary": "Deleted the 'y.x' assignment", - "tag": "JSONSummary" + "summary": "Deleted the 'y.x' assignment" }, { "span": { @@ -216,8 +209,7 @@ ] } }, - "summary": "Added the 'y.x' assignment", - "tag": "JSONSummary" + "summary": "Added the 'y.x' assignment" } ] }, @@ -226,9 +218,9 @@ "filePaths": [ "member-access-assignment.js" ], - "sha1": "24e43482adbbe8bdbb56191bc3b2ac1387049f77", + "sha1": "62c47a061654573bb752aae3bd9ef9bcceaddf20", "gitDir": "test/corpus/repos/javascript", - "sha2": "ec5bc8a34cb2ac731d35de1a1ef2a41f479d9085" + "sha2": "19c82c7fd6b8e019cf970ad495af8c0998610f6f" } ,{ "testCaseDescription": "javascript-member-access-assignment-delete-test", @@ -248,8 +240,7 @@ ] } }, - "summary": "Deleted the 'y.x' assignment", - "tag": "JSONSummary" + "summary": "Deleted the 'y.x' assignment" } ] }, @@ -258,9 +249,9 @@ "filePaths": [ "member-access-assignment.js" ], - "sha1": "ec5bc8a34cb2ac731d35de1a1ef2a41f479d9085", + "sha1": "19c82c7fd6b8e019cf970ad495af8c0998610f6f", "gitDir": "test/corpus/repos/javascript", - "sha2": "17c753388d910dee728182ae1a1f3ad9fdce2616" + "sha2": "c87076b2cfb63f72f222f023fe8aa0d28927632a" } ,{ "testCaseDescription": "javascript-member-access-assignment-delete-rest-test", @@ -280,8 +271,7 @@ ] } }, - "summary": "Deleted the 'y.x' assignment", - "tag": "JSONSummary" + "summary": "Deleted the 'y.x' assignment" } ] }, @@ -290,7 +280,7 @@ "filePaths": [ "member-access-assignment.js" ], - "sha1": "17c753388d910dee728182ae1a1f3ad9fdce2616", + "sha1": "c87076b2cfb63f72f222f023fe8aa0d28927632a", "gitDir": "test/corpus/repos/javascript", - "sha2": "43c155e0e1c235f4a7a66d19b55ec670aa456167" + "sha2": "9ca89bc6c9066b34bc18aecce4f646208c65c907" }] diff --git a/test/corpus/diff-summaries/javascript/member-access.json b/test/corpus/diff-summaries/javascript/member-access.json index 2b1e45650..4839d85b4 100644 --- a/test/corpus/diff-summaries/javascript/member-access.json +++ b/test/corpus/diff-summaries/javascript/member-access.json @@ -16,8 +16,7 @@ ] } }, - "summary": "Added the 'x.someProperty' member access", - "tag": "JSONSummary" + "summary": "Added the 'x.someProperty' member access" } ] }, @@ -26,9 +25,9 @@ "filePaths": [ "member-access.js" ], - "sha1": "34dda706308957a43236571644aff6e35d5ed5c8", + "sha1": "8c89ac29c02f4714dc946e2824152d320b623e36", "gitDir": "test/corpus/repos/javascript", - "sha2": "229478a3867e3a976746a8e8e30e79ed9383d47b" + "sha2": "7819fe045b5f19ee470b8f0d2371d9344f6c183a" } ,{ "testCaseDescription": "javascript-member-access-replacement-insert-test", @@ -48,8 +47,7 @@ ] } }, - "summary": "Added the 'x.someOtherProperty' member access", - "tag": "JSONSummary" + "summary": "Added the 'x.someOtherProperty' member access" }, { "span": { @@ -64,8 +62,7 @@ ] } }, - "summary": "Added the 'x.someProperty' member access", - "tag": "JSONSummary" + "summary": "Added the 'x.someProperty' member access" } ] }, @@ -74,9 +71,9 @@ "filePaths": [ "member-access.js" ], - "sha1": "229478a3867e3a976746a8e8e30e79ed9383d47b", + "sha1": "7819fe045b5f19ee470b8f0d2371d9344f6c183a", "gitDir": "test/corpus/repos/javascript", - "sha2": "77a6c524dc810aef2a026ada74ae51db6401d399" + "sha2": "823d52271b2d99c48216948e20cec0ba6b9d1e6e" } ,{ "testCaseDescription": "javascript-member-access-delete-insert-test", @@ -108,8 +105,7 @@ } ] }, - "summary": "Replaced the 'someOtherProperty' identifier with the 'someProperty' identifier", - "tag": "JSONSummary" + "summary": "Replaced the 'someOtherProperty' identifier with the 'someProperty' identifier" } ] }, @@ -118,9 +114,9 @@ "filePaths": [ "member-access.js" ], - "sha1": "77a6c524dc810aef2a026ada74ae51db6401d399", + "sha1": "823d52271b2d99c48216948e20cec0ba6b9d1e6e", "gitDir": "test/corpus/repos/javascript", - "sha2": "a24d2c73c061cc1124a76c8d53d324f6d8d56b1b" + "sha2": "dd0030c04fcaf1e5784706aee9760bd9904495b8" } ,{ "testCaseDescription": "javascript-member-access-replacement-test", @@ -152,8 +148,7 @@ } ] }, - "summary": "Replaced the 'someProperty' identifier with the 'someOtherProperty' identifier", - "tag": "JSONSummary" + "summary": "Replaced the 'someProperty' identifier with the 'someOtherProperty' identifier" } ] }, @@ -162,9 +157,9 @@ "filePaths": [ "member-access.js" ], - "sha1": "a24d2c73c061cc1124a76c8d53d324f6d8d56b1b", + "sha1": "dd0030c04fcaf1e5784706aee9760bd9904495b8", "gitDir": "test/corpus/repos/javascript", - "sha2": "397d55476cc1b66ae98e4f258055a0a5a6860f4c" + "sha2": "88e2ad3ffa0cca807aeb6e2ea97562c04034a954" } ,{ "testCaseDescription": "javascript-member-access-delete-replacement-test", @@ -184,8 +179,7 @@ ] } }, - "summary": "Deleted the 'x.someOtherProperty' member access", - "tag": "JSONSummary" + "summary": "Deleted the 'x.someOtherProperty' member access" }, { "span": { @@ -200,8 +194,7 @@ ] } }, - "summary": "Deleted the 'x.someProperty' member access", - "tag": "JSONSummary" + "summary": "Deleted the 'x.someProperty' member access" }, { "span": { @@ -216,8 +209,7 @@ ] } }, - "summary": "Added the 'x.someOtherProperty' member access", - "tag": "JSONSummary" + "summary": "Added the 'x.someOtherProperty' member access" } ] }, @@ -226,9 +218,9 @@ "filePaths": [ "member-access.js" ], - "sha1": "397d55476cc1b66ae98e4f258055a0a5a6860f4c", + "sha1": "88e2ad3ffa0cca807aeb6e2ea97562c04034a954", "gitDir": "test/corpus/repos/javascript", - "sha2": "5677ae58e398c0c1918513007208da0fdf21e181" + "sha2": "2aaeaae2047b4dea6cb7f6a0851e0314b682b856" } ,{ "testCaseDescription": "javascript-member-access-delete-test", @@ -248,8 +240,7 @@ ] } }, - "summary": "Deleted the 'x.someProperty' member access", - "tag": "JSONSummary" + "summary": "Deleted the 'x.someProperty' member access" } ] }, @@ -258,9 +249,9 @@ "filePaths": [ "member-access.js" ], - "sha1": "5677ae58e398c0c1918513007208da0fdf21e181", + "sha1": "2aaeaae2047b4dea6cb7f6a0851e0314b682b856", "gitDir": "test/corpus/repos/javascript", - "sha2": "9b5bb8a95ace1c7bf6b2017bacaaf538c41508b5" + "sha2": "5ee7c25fc11122ae36f4a585fafbe0d0f69ed1b9" } ,{ "testCaseDescription": "javascript-member-access-delete-rest-test", @@ -280,8 +271,7 @@ ] } }, - "summary": "Deleted the 'x.someOtherProperty' member access", - "tag": "JSONSummary" + "summary": "Deleted the 'x.someOtherProperty' member access" } ] }, @@ -290,7 +280,7 @@ "filePaths": [ "member-access.js" ], - "sha1": "9b5bb8a95ace1c7bf6b2017bacaaf538c41508b5", + "sha1": "5ee7c25fc11122ae36f4a585fafbe0d0f69ed1b9", "gitDir": "test/corpus/repos/javascript", - "sha2": "13bf09743306aea0c956273f7ead3bc1759bcee5" + "sha2": "b5aeb51a21b78d1547cc65d09bad74c4e27f68c6" }] diff --git a/test/corpus/diff-summaries/javascript/method-call.json b/test/corpus/diff-summaries/javascript/method-call.json index db69e239e..6c6ad789e 100644 --- a/test/corpus/diff-summaries/javascript/method-call.json +++ b/test/corpus/diff-summaries/javascript/method-call.json @@ -16,8 +16,7 @@ ] } }, - "summary": "Added the 'object.someMethod(arg1, \"arg2\")' method call", - "tag": "JSONSummary" + "summary": "Added the 'object.someMethod(arg1, \"arg2\")' method call" } ] }, @@ -26,9 +25,9 @@ "filePaths": [ "method-call.js" ], - "sha1": "bd15264892a7cee21de72ea983762c38c1f900b7", + "sha1": "a37267842ee6f1e161c4316af0cb35f4b632a059", "gitDir": "test/corpus/repos/javascript", - "sha2": "3cc7d50b45588156ba2ffcfa2d5af9ad12a00b9b" + "sha2": "609913d4f6d79ee00e3d411b2e3915071ad635f5" } ,{ "testCaseDescription": "javascript-method-call-replacement-insert-test", @@ -48,8 +47,7 @@ ] } }, - "summary": "Added the 'object.someMethod(arg1, \"arg3\")' method call", - "tag": "JSONSummary" + "summary": "Added the 'object.someMethod(arg1, \"arg3\")' method call" }, { "span": { @@ -64,8 +62,7 @@ ] } }, - "summary": "Added the 'object.someMethod(arg1, \"arg2\")' method call", - "tag": "JSONSummary" + "summary": "Added the 'object.someMethod(arg1, \"arg2\")' method call" } ] }, @@ -74,9 +71,9 @@ "filePaths": [ "method-call.js" ], - "sha1": "3cc7d50b45588156ba2ffcfa2d5af9ad12a00b9b", + "sha1": "609913d4f6d79ee00e3d411b2e3915071ad635f5", "gitDir": "test/corpus/repos/javascript", - "sha2": "6475c883d4ed36ef6f15fa3e3a12ff893f728264" + "sha2": "33a0c4183dd058b371cce8b43c01dc788edd30f2" } ,{ "testCaseDescription": "javascript-method-call-delete-insert-test", @@ -108,8 +105,7 @@ } ] }, - "summary": "Replaced the \"arg3\" string with the \"arg2\" string in the object.someMethod(arg1, \"arg2\") method call", - "tag": "JSONSummary" + "summary": "Replaced the \"arg3\" string with the \"arg2\" string in the object.someMethod(arg1, \"arg2\") method call" } ] }, @@ -118,9 +114,9 @@ "filePaths": [ "method-call.js" ], - "sha1": "6475c883d4ed36ef6f15fa3e3a12ff893f728264", + "sha1": "33a0c4183dd058b371cce8b43c01dc788edd30f2", "gitDir": "test/corpus/repos/javascript", - "sha2": "efc3bb8710951cd60a0535ffc790eb411415c39f" + "sha2": "b350dc1500aa52926e6cd6fedc4e04375a2f3828" } ,{ "testCaseDescription": "javascript-method-call-replacement-test", @@ -152,8 +148,7 @@ } ] }, - "summary": "Replaced the \"arg2\" string with the \"arg3\" string in the object.someMethod(arg1, \"arg3\") method call", - "tag": "JSONSummary" + "summary": "Replaced the \"arg2\" string with the \"arg3\" string in the object.someMethod(arg1, \"arg3\") method call" } ] }, @@ -162,9 +157,9 @@ "filePaths": [ "method-call.js" ], - "sha1": "efc3bb8710951cd60a0535ffc790eb411415c39f", + "sha1": "b350dc1500aa52926e6cd6fedc4e04375a2f3828", "gitDir": "test/corpus/repos/javascript", - "sha2": "92f66e257a70c7c4cfe02a2b740c995018679430" + "sha2": "ee87a9ae5d5c4a2518eb5f7ef0b26bd9b0a371e6" } ,{ "testCaseDescription": "javascript-method-call-delete-replacement-test", @@ -184,8 +179,7 @@ ] } }, - "summary": "Deleted the 'object.someMethod(arg1, \"arg3\")' method call", - "tag": "JSONSummary" + "summary": "Deleted the 'object.someMethod(arg1, \"arg3\")' method call" }, { "span": { @@ -200,8 +194,7 @@ ] } }, - "summary": "Deleted the 'object.someMethod(arg1, \"arg2\")' method call", - "tag": "JSONSummary" + "summary": "Deleted the 'object.someMethod(arg1, \"arg2\")' method call" }, { "span": { @@ -216,8 +209,7 @@ ] } }, - "summary": "Added the 'object.someMethod(arg1, \"arg3\")' method call", - "tag": "JSONSummary" + "summary": "Added the 'object.someMethod(arg1, \"arg3\")' method call" } ] }, @@ -226,9 +218,9 @@ "filePaths": [ "method-call.js" ], - "sha1": "92f66e257a70c7c4cfe02a2b740c995018679430", + "sha1": "ee87a9ae5d5c4a2518eb5f7ef0b26bd9b0a371e6", "gitDir": "test/corpus/repos/javascript", - "sha2": "be9128442aa9fe04e0d8adf7d386c09b65c0dc68" + "sha2": "794adc95ac0d89beca54fc417b94eaf5ac50ec58" } ,{ "testCaseDescription": "javascript-method-call-delete-test", @@ -248,8 +240,7 @@ ] } }, - "summary": "Deleted the 'object.someMethod(arg1, \"arg2\")' method call", - "tag": "JSONSummary" + "summary": "Deleted the 'object.someMethod(arg1, \"arg2\")' method call" } ] }, @@ -258,9 +249,9 @@ "filePaths": [ "method-call.js" ], - "sha1": "be9128442aa9fe04e0d8adf7d386c09b65c0dc68", + "sha1": "794adc95ac0d89beca54fc417b94eaf5ac50ec58", "gitDir": "test/corpus/repos/javascript", - "sha2": "2d65956f15bf31fbf63e5c67b1b1d9c23a233b5a" + "sha2": "db28776718addccb53343bee695b484d8a389784" } ,{ "testCaseDescription": "javascript-method-call-delete-rest-test", @@ -280,8 +271,7 @@ ] } }, - "summary": "Deleted the 'object.someMethod(arg1, \"arg3\")' method call", - "tag": "JSONSummary" + "summary": "Deleted the 'object.someMethod(arg1, \"arg3\")' method call" } ] }, @@ -290,7 +280,7 @@ "filePaths": [ "method-call.js" ], - "sha1": "2d65956f15bf31fbf63e5c67b1b1d9c23a233b5a", + "sha1": "db28776718addccb53343bee695b484d8a389784", "gitDir": "test/corpus/repos/javascript", - "sha2": "e1bef609317c32e852d5067ed84baeea51868e53" + "sha2": "7b45d5b720f557df4fbd880be8c0e292c4defdc4" }] diff --git a/test/corpus/diff-summaries/javascript/named-function.json b/test/corpus/diff-summaries/javascript/named-function.json index b220803ca..235f6a373 100644 --- a/test/corpus/diff-summaries/javascript/named-function.json +++ b/test/corpus/diff-summaries/javascript/named-function.json @@ -16,8 +16,7 @@ ] } }, - "summary": "Added the 'myFunction' function", - "tag": "JSONSummary" + "summary": "Added the 'myFunction' function" } ] }, @@ -26,9 +25,9 @@ "filePaths": [ "named-function.js" ], - "sha1": "9e9c5e08a862128a46c888405ef29a584da0e923", + "sha1": "caeacf57ee751440e4f9b9f606df460c17499bdd", "gitDir": "test/corpus/repos/javascript", - "sha2": "f31cd7b33a288a75aa8d5b0d3488c0de723cb5dd" + "sha2": "742ee12fc034748905977d3e1ba7818df34b9b66" } ,{ "testCaseDescription": "javascript-named-function-replacement-insert-test", @@ -48,8 +47,7 @@ ] } }, - "summary": "Added the 'anotherFunction' function", - "tag": "JSONSummary" + "summary": "Added the 'anotherFunction' function" }, { "span": { @@ -64,8 +62,7 @@ ] } }, - "summary": "Added the 'myFunction' function", - "tag": "JSONSummary" + "summary": "Added the 'myFunction' function" } ] }, @@ -74,9 +71,9 @@ "filePaths": [ "named-function.js" ], - "sha1": "f31cd7b33a288a75aa8d5b0d3488c0de723cb5dd", + "sha1": "742ee12fc034748905977d3e1ba7818df34b9b66", "gitDir": "test/corpus/repos/javascript", - "sha2": "a4e9ee32075f16e11f34bef7a33851a493f688ee" + "sha2": "05f7b98428d31fa7ae97f65b6c901b8b392764f7" } ,{ "testCaseDescription": "javascript-named-function-delete-insert-test", @@ -108,8 +105,7 @@ } ] }, - "summary": "Replaced the 'anotherFunction' identifier with the 'myFunction' identifier in the myFunction function", - "tag": "JSONSummary" + "summary": "Replaced the 'anotherFunction' identifier with the 'myFunction' identifier in the myFunction function" }, { "span": { @@ -124,8 +120,7 @@ ] } }, - "summary": "Added the 'arg1' identifier in the myFunction function", - "tag": "JSONSummary" + "summary": "Added the 'arg1' identifier in the myFunction function" }, { "span": { @@ -140,8 +135,7 @@ ] } }, - "summary": "Added the 'arg2' identifier in the myFunction function", - "tag": "JSONSummary" + "summary": "Added the 'arg2' identifier in the myFunction function" }, { "span": { @@ -156,8 +150,7 @@ ] } }, - "summary": "Added the 'arg2' identifier in the myFunction function", - "tag": "JSONSummary" + "summary": "Added the 'arg2' identifier in the myFunction function" }, { "span": { @@ -172,8 +165,7 @@ ] } }, - "summary": "Deleted the 'false' return statement in the myFunction function", - "tag": "JSONSummary" + "summary": "Deleted the 'false' return statement in the myFunction function" } ] }, @@ -182,9 +174,9 @@ "filePaths": [ "named-function.js" ], - "sha1": "a4e9ee32075f16e11f34bef7a33851a493f688ee", + "sha1": "05f7b98428d31fa7ae97f65b6c901b8b392764f7", "gitDir": "test/corpus/repos/javascript", - "sha2": "4de27cb3698e46c8c941c58e677cfe3d8ab48078" + "sha2": "e60e4118dca7f21ef5d06d668e6f6961f94ece60" } ,{ "testCaseDescription": "javascript-named-function-replacement-test", @@ -216,8 +208,7 @@ } ] }, - "summary": "Replaced the 'myFunction' identifier with the 'anotherFunction' identifier in the anotherFunction function", - "tag": "JSONSummary" + "summary": "Replaced the 'myFunction' identifier with the 'anotherFunction' identifier in the anotherFunction function" }, { "span": { @@ -232,8 +223,7 @@ ] } }, - "summary": "Deleted the 'arg1' identifier in the anotherFunction function", - "tag": "JSONSummary" + "summary": "Deleted the 'arg1' identifier in the anotherFunction function" }, { "span": { @@ -248,8 +238,7 @@ ] } }, - "summary": "Deleted the 'arg2' identifier in the anotherFunction function", - "tag": "JSONSummary" + "summary": "Deleted the 'arg2' identifier in the anotherFunction function" }, { "span": { @@ -264,8 +253,7 @@ ] } }, - "summary": "Added the 'false' return statement in the anotherFunction function", - "tag": "JSONSummary" + "summary": "Added the 'false' return statement in the anotherFunction function" }, { "span": { @@ -280,8 +268,7 @@ ] } }, - "summary": "Deleted the 'arg2' identifier in the anotherFunction function", - "tag": "JSONSummary" + "summary": "Deleted the 'arg2' identifier in the anotherFunction function" } ] }, @@ -290,9 +277,9 @@ "filePaths": [ "named-function.js" ], - "sha1": "4de27cb3698e46c8c941c58e677cfe3d8ab48078", + "sha1": "e60e4118dca7f21ef5d06d668e6f6961f94ece60", "gitDir": "test/corpus/repos/javascript", - "sha2": "c947b40e91668836ccb2dcb0aa705ae25b5c9509" + "sha2": "0d662b70bd31f4c7a957db6e3c874f0e117d81ec" } ,{ "testCaseDescription": "javascript-named-function-delete-replacement-test", @@ -312,8 +299,7 @@ ] } }, - "summary": "Deleted the 'anotherFunction' function", - "tag": "JSONSummary" + "summary": "Deleted the 'anotherFunction' function" }, { "span": { @@ -328,8 +314,7 @@ ] } }, - "summary": "Deleted the 'myFunction' function", - "tag": "JSONSummary" + "summary": "Deleted the 'myFunction' function" }, { "span": { @@ -344,8 +329,7 @@ ] } }, - "summary": "Added the 'anotherFunction' function", - "tag": "JSONSummary" + "summary": "Added the 'anotherFunction' function" } ] }, @@ -354,9 +338,9 @@ "filePaths": [ "named-function.js" ], - "sha1": "c947b40e91668836ccb2dcb0aa705ae25b5c9509", + "sha1": "0d662b70bd31f4c7a957db6e3c874f0e117d81ec", "gitDir": "test/corpus/repos/javascript", - "sha2": "2e880b7e68923075fc2c7c8b61534af7afa3ea44" + "sha2": "2751fd48810beeaf43dbb897d5687e7bb4605ee8" } ,{ "testCaseDescription": "javascript-named-function-delete-test", @@ -376,8 +360,7 @@ ] } }, - "summary": "Deleted the 'myFunction' function", - "tag": "JSONSummary" + "summary": "Deleted the 'myFunction' function" } ] }, @@ -386,9 +369,9 @@ "filePaths": [ "named-function.js" ], - "sha1": "2e880b7e68923075fc2c7c8b61534af7afa3ea44", + "sha1": "2751fd48810beeaf43dbb897d5687e7bb4605ee8", "gitDir": "test/corpus/repos/javascript", - "sha2": "a298f3ad3bab2182e5d50a6908514d6ad210d5a9" + "sha2": "71fbb6e60978e220e6e2f91e426df58fc0fd8317" } ,{ "testCaseDescription": "javascript-named-function-delete-rest-test", @@ -408,8 +391,7 @@ ] } }, - "summary": "Deleted the 'anotherFunction' function", - "tag": "JSONSummary" + "summary": "Deleted the 'anotherFunction' function" } ] }, @@ -418,7 +400,7 @@ "filePaths": [ "named-function.js" ], - "sha1": "a298f3ad3bab2182e5d50a6908514d6ad210d5a9", + "sha1": "71fbb6e60978e220e6e2f91e426df58fc0fd8317", "gitDir": "test/corpus/repos/javascript", - "sha2": "00345376742839aaf8cdbefbe8cb10795489044a" + "sha2": "224d24020b3b8d08a8f3aced4b83b49a5779ba41" }] diff --git a/test/corpus/diff-summaries/javascript/nested-do-while-in-function.json b/test/corpus/diff-summaries/javascript/nested-do-while-in-function.json index c43d91fd1..aaacc9ba6 100644 --- a/test/corpus/diff-summaries/javascript/nested-do-while-in-function.json +++ b/test/corpus/diff-summaries/javascript/nested-do-while-in-function.json @@ -16,8 +16,7 @@ ] } }, - "summary": "Added the name1, name2, name3, nameN export statement", - "tag": "JSONSummary" + "summary": "Added the name1, name2, name3, nameN export statement" }, { "span": { @@ -32,8 +31,7 @@ ] } }, - "summary": "Added the variable1 as name1, variable2 as name2, nameN export statement", - "tag": "JSONSummary" + "summary": "Added the variable1 as name1, variable2 as name2, nameN export statement" }, { "span": { @@ -48,8 +46,7 @@ ] } }, - "summary": "Added the name1, name2, nameN export statement", - "tag": "JSONSummary" + "summary": "Added the name1, name2, nameN export statement" }, { "span": { @@ -64,8 +61,7 @@ ] } }, - "summary": "Added the name1 = value1, name2 = value2, name3, nameN export statement", - "tag": "JSONSummary" + "summary": "Added the name1 = value1, name2 = value2, name3, nameN export statement" }, { "span": { @@ -80,8 +76,7 @@ ] } }, - "summary": "Added the namedFunction export statement", - "tag": "JSONSummary" + "summary": "Added the namedFunction export statement" }, { "span": { @@ -96,8 +91,7 @@ ] } }, - "summary": "Added the anonymous() function export statement", - "tag": "JSONSummary" + "summary": "Added the anonymous() function export statement" }, { "span": { @@ -112,8 +106,7 @@ ] } }, - "summary": "Added the name1 export statement", - "tag": "JSONSummary" + "summary": "Added the name1 export statement" }, { "span": { @@ -128,8 +121,7 @@ ] } }, - "summary": "Added the name1 as default export statement", - "tag": "JSONSummary" + "summary": "Added the name1 as default export statement" }, { "span": { @@ -144,8 +136,7 @@ ] } }, - "summary": "Added the 'foo' export statement", - "tag": "JSONSummary" + "summary": "Added the 'foo' export statement" }, { "span": { @@ -160,8 +151,7 @@ ] } }, - "summary": "Added the name1, name2, nameN from 'foo' export statement", - "tag": "JSONSummary" + "summary": "Added the name1, name2, nameN from 'foo' export statement" }, { "span": { @@ -176,8 +166,7 @@ ] } }, - "summary": "Added the import1 as name1, import2 as name2, nameN from 'bar' export statement", - "tag": "JSONSummary" + "summary": "Added the import1 as name1, import2 as name2, nameN from 'bar' export statement" } ] }, @@ -186,9 +175,9 @@ "filePaths": [ "export.js" ], - "sha1": "cf784ad9d8d9843aa79915afc98e7c8c7def3bce", + "sha1": "325e137487dbe6b99e8736817eaf2d7b25572dc8", "gitDir": "test/corpus/repos/javascript", - "sha2": "6a61c15ee9b892ad6fb99edf5ed4fddaaf1668cd" + "sha2": "5cc80139b82de7b04677ae393b72bfb45d5c2a15" } ,{ "testCaseDescription": "javascript-export-replacement-insert-test", @@ -208,8 +197,7 @@ ] } }, - "summary": "Added the name4, name5, name6, nameZ export statement", - "tag": "JSONSummary" + "summary": "Added the name4, name5, name6, nameZ export statement" }, { "span": { @@ -224,8 +212,7 @@ ] } }, - "summary": "Added the variable2 as name2, variable3 as name3, nameY export statement", - "tag": "JSONSummary" + "summary": "Added the variable2 as name2, variable3 as name3, nameY export statement" }, { "span": { @@ -240,8 +227,7 @@ ] } }, - "summary": "Added the name3, name4, nameT export statement", - "tag": "JSONSummary" + "summary": "Added the name3, name4, nameT export statement" }, { "span": { @@ -256,8 +242,7 @@ ] } }, - "summary": "Added the name2 = value2, name3 = value3, name4, nameO export statement", - "tag": "JSONSummary" + "summary": "Added the name2 = value2, name3 = value3, name4, nameO export statement" }, { "span": { @@ -272,8 +257,7 @@ ] } }, - "summary": "Added the otherNamedFunction export statement", - "tag": "JSONSummary" + "summary": "Added the otherNamedFunction export statement" }, { "span": { @@ -288,8 +272,7 @@ ] } }, - "summary": "Added the newName1 export statement", - "tag": "JSONSummary" + "summary": "Added the newName1 export statement" }, { "span": { @@ -304,8 +287,7 @@ ] } }, - "summary": "Added the anonymous() function export statement", - "tag": "JSONSummary" + "summary": "Added the anonymous() function export statement" }, { "span": { @@ -320,8 +302,7 @@ ] } }, - "summary": "Added the name2 as statement export statement", - "tag": "JSONSummary" + "summary": "Added the name2 as statement export statement" }, { "span": { @@ -336,8 +317,7 @@ ] } }, - "summary": "Added the 'baz' export statement", - "tag": "JSONSummary" + "summary": "Added the 'baz' export statement" }, { "span": { @@ -352,8 +332,7 @@ ] } }, - "summary": "Added the name7, name8, nameP from 'buzz' export statement", - "tag": "JSONSummary" + "summary": "Added the name7, name8, nameP from 'buzz' export statement" }, { "span": { @@ -368,8 +347,7 @@ ] } }, - "summary": "Added the import6 as name6, import7 as name7, nameB from 'fizz' export statement", - "tag": "JSONSummary" + "summary": "Added the import6 as name6, import7 as name7, nameB from 'fizz' export statement" }, { "span": { @@ -384,8 +362,7 @@ ] } }, - "summary": "Added the name1, name2, name3, nameN export statement", - "tag": "JSONSummary" + "summary": "Added the name1, name2, name3, nameN export statement" }, { "span": { @@ -400,8 +377,7 @@ ] } }, - "summary": "Added the variable1 as name1, variable2 as name2, nameN export statement", - "tag": "JSONSummary" + "summary": "Added the variable1 as name1, variable2 as name2, nameN export statement" }, { "span": { @@ -416,8 +392,7 @@ ] } }, - "summary": "Added the name1, name2, nameN export statement", - "tag": "JSONSummary" + "summary": "Added the name1, name2, nameN export statement" }, { "span": { @@ -432,8 +407,7 @@ ] } }, - "summary": "Added the name1 = value1, name2 = value2, name3, nameN export statement", - "tag": "JSONSummary" + "summary": "Added the name1 = value1, name2 = value2, name3, nameN export statement" }, { "span": { @@ -448,8 +422,7 @@ ] } }, - "summary": "Added the namedFunction export statement", - "tag": "JSONSummary" + "summary": "Added the namedFunction export statement" }, { "span": { @@ -464,8 +437,7 @@ ] } }, - "summary": "Added the anonymous() function export statement", - "tag": "JSONSummary" + "summary": "Added the anonymous() function export statement" }, { "span": { @@ -480,8 +452,7 @@ ] } }, - "summary": "Added the name1 export statement", - "tag": "JSONSummary" + "summary": "Added the name1 export statement" }, { "span": { @@ -496,8 +467,7 @@ ] } }, - "summary": "Added the name1 as default export statement", - "tag": "JSONSummary" + "summary": "Added the name1 as default export statement" }, { "span": { @@ -512,8 +482,7 @@ ] } }, - "summary": "Added the 'foo' export statement", - "tag": "JSONSummary" + "summary": "Added the 'foo' export statement" }, { "span": { @@ -528,8 +497,7 @@ ] } }, - "summary": "Added the name1, name2, nameN from 'foo' export statement", - "tag": "JSONSummary" + "summary": "Added the name1, name2, nameN from 'foo' export statement" }, { "span": { @@ -544,8 +512,7 @@ ] } }, - "summary": "Added the import1 as name1, import2 as name2, nameN from 'bar' export statement", - "tag": "JSONSummary" + "summary": "Added the import1 as name1, import2 as name2, nameN from 'bar' export statement" } ] }, @@ -554,9 +521,9 @@ "filePaths": [ "export.js" ], - "sha1": "6a61c15ee9b892ad6fb99edf5ed4fddaaf1668cd", + "sha1": "5cc80139b82de7b04677ae393b72bfb45d5c2a15", "gitDir": "test/corpus/repos/javascript", - "sha2": "8b44c437b4f4230802f75d171dfe1e45a5131045" + "sha2": "4a8a60bc1bf98a633b4c92368a075c7990b983d7" } ,{ "testCaseDescription": "javascript-export-delete-insert-test", @@ -588,8 +555,7 @@ } ] }, - "summary": "Replaced the 'name4' identifier with the 'name1' identifier in the name1, name2, name3, nameN export statement", - "tag": "JSONSummary" + "summary": "Replaced the 'name4' identifier with the 'name1' identifier in the name1, name2, name3, nameN export statement" }, { "span": { @@ -616,8 +582,7 @@ } ] }, - "summary": "Replaced the 'name5' identifier with the 'name2' identifier in the name1, name2, name3, nameN export statement", - "tag": "JSONSummary" + "summary": "Replaced the 'name5' identifier with the 'name2' identifier in the name1, name2, name3, nameN export statement" }, { "span": { @@ -644,8 +609,7 @@ } ] }, - "summary": "Replaced the 'name6' identifier with the 'name3' identifier in the name1, name2, name3, nameN export statement", - "tag": "JSONSummary" + "summary": "Replaced the 'name6' identifier with the 'name3' identifier in the name1, name2, name3, nameN export statement" }, { "span": { @@ -672,8 +636,7 @@ } ] }, - "summary": "Replaced the 'nameZ' identifier with the 'nameN' identifier in the name1, name2, name3, nameN export statement", - "tag": "JSONSummary" + "summary": "Replaced the 'nameZ' identifier with the 'nameN' identifier in the name1, name2, name3, nameN export statement" }, { "span": { @@ -700,8 +663,7 @@ } ] }, - "summary": "Replaced the 'variable2' identifier with the 'variable1' identifier in the variable1 as name1, variable2 as name2, nameN export statement", - "tag": "JSONSummary" + "summary": "Replaced the 'variable2' identifier with the 'variable1' identifier in the variable1 as name1, variable2 as name2, nameN export statement" }, { "span": { @@ -728,8 +690,7 @@ } ] }, - "summary": "Replaced the 'name2' identifier with the 'name1' identifier in the variable1 as name1, variable2 as name2, nameN export statement", - "tag": "JSONSummary" + "summary": "Replaced the 'name2' identifier with the 'name1' identifier in the variable1 as name1, variable2 as name2, nameN export statement" }, { "span": { @@ -756,8 +717,7 @@ } ] }, - "summary": "Replaced the 'variable3' identifier with the 'variable2' identifier in the variable1 as name1, variable2 as name2, nameN export statement", - "tag": "JSONSummary" + "summary": "Replaced the 'variable3' identifier with the 'variable2' identifier in the variable1 as name1, variable2 as name2, nameN export statement" }, { "span": { @@ -784,8 +744,7 @@ } ] }, - "summary": "Replaced the 'name3' identifier with the 'name2' identifier in the variable1 as name1, variable2 as name2, nameN export statement", - "tag": "JSONSummary" + "summary": "Replaced the 'name3' identifier with the 'name2' identifier in the variable1 as name1, variable2 as name2, nameN export statement" }, { "span": { @@ -812,8 +771,7 @@ } ] }, - "summary": "Replaced the 'nameY' identifier with the 'nameN' identifier in the variable1 as name1, variable2 as name2, nameN export statement", - "tag": "JSONSummary" + "summary": "Replaced the 'nameY' identifier with the 'nameN' identifier in the variable1 as name1, variable2 as name2, nameN export statement" }, { "span": { @@ -840,8 +798,7 @@ } ] }, - "summary": "Replaced the 'name3' identifier with the 'name1' identifier in the name1, name2, nameN export statement", - "tag": "JSONSummary" + "summary": "Replaced the 'name3' identifier with the 'name1' identifier in the name1, name2, nameN export statement" }, { "span": { @@ -868,8 +825,7 @@ } ] }, - "summary": "Replaced the 'name4' identifier with the 'name2' identifier in the name1, name2, nameN export statement", - "tag": "JSONSummary" + "summary": "Replaced the 'name4' identifier with the 'name2' identifier in the name1, name2, nameN export statement" }, { "span": { @@ -896,8 +852,7 @@ } ] }, - "summary": "Replaced the 'nameT' identifier with the 'nameN' identifier in the name1, name2, nameN export statement", - "tag": "JSONSummary" + "summary": "Replaced the 'nameT' identifier with the 'nameN' identifier in the name1, name2, nameN export statement" }, { "span": { @@ -924,8 +879,7 @@ } ] }, - "summary": "Replaced the 'name2' identifier with the 'name1' identifier in the name1 var assignment", - "tag": "JSONSummary" + "summary": "Replaced the 'name2' identifier with the 'name1' identifier in the name1 var assignment" }, { "span": { @@ -952,8 +906,7 @@ } ] }, - "summary": "Replaced the 'value2' identifier with the 'value1' identifier in the name1 var assignment", - "tag": "JSONSummary" + "summary": "Replaced the 'value2' identifier with the 'value1' identifier in the name1 var assignment" }, { "span": { @@ -980,8 +933,7 @@ } ] }, - "summary": "Replaced the 'name3' identifier with the 'name2' identifier in the name2 var assignment", - "tag": "JSONSummary" + "summary": "Replaced the 'name3' identifier with the 'name2' identifier in the name2 var assignment" }, { "span": { @@ -1008,8 +960,7 @@ } ] }, - "summary": "Replaced the 'value3' identifier with the 'value2' identifier in the name2 var assignment", - "tag": "JSONSummary" + "summary": "Replaced the 'value3' identifier with the 'value2' identifier in the name2 var assignment" }, { "span": { @@ -1036,8 +987,7 @@ } ] }, - "summary": "Replaced the 'name4' identifier with the 'name3' identifier in the name1 = value1, name2 = value2, name3, nameN export statement", - "tag": "JSONSummary" + "summary": "Replaced the 'name4' identifier with the 'name3' identifier in the name1 = value1, name2 = value2, name3, nameN export statement" }, { "span": { @@ -1064,8 +1014,7 @@ } ] }, - "summary": "Replaced the 'nameO' identifier with the 'nameN' identifier in the name1 = value1, name2 = value2, name3, nameN export statement", - "tag": "JSONSummary" + "summary": "Replaced the 'nameO' identifier with the 'nameN' identifier in the name1 = value1, name2 = value2, name3, nameN export statement" }, { "span": { @@ -1092,8 +1041,7 @@ } ] }, - "summary": "Replaced the 'otherNamedFunction' identifier with the 'namedFunction' identifier in the namedFunction export statement", - "tag": "JSONSummary" + "summary": "Replaced the 'otherNamedFunction' identifier with the 'namedFunction' identifier in the namedFunction export statement" }, { "span": { @@ -1108,8 +1056,7 @@ ] } }, - "summary": "Added the anonymous() function export statement", - "tag": "JSONSummary" + "summary": "Added the anonymous() function export statement" }, { "span": { @@ -1124,8 +1071,7 @@ ] } }, - "summary": "Added the name1 export statement", - "tag": "JSONSummary" + "summary": "Added the name1 export statement" }, { "span": { @@ -1140,8 +1086,7 @@ ] } }, - "summary": "Added the name1 as default export statement", - "tag": "JSONSummary" + "summary": "Added the name1 as default export statement" }, { "span": { @@ -1156,8 +1101,7 @@ ] } }, - "summary": "Added the 'foo' export statement", - "tag": "JSONSummary" + "summary": "Added the 'foo' export statement" }, { "span": { @@ -1172,8 +1116,7 @@ ] } }, - "summary": "Added the name1, name2, nameN from 'foo' export statement", - "tag": "JSONSummary" + "summary": "Added the name1, name2, nameN from 'foo' export statement" }, { "span": { @@ -1188,8 +1131,7 @@ ] } }, - "summary": "Added the import1 as name1, import2 as name2, nameN from 'bar' export statement", - "tag": "JSONSummary" + "summary": "Added the import1 as name1, import2 as name2, nameN from 'bar' export statement" }, { "span": { @@ -1204,8 +1146,7 @@ ] } }, - "summary": "Deleted the newName1 export statement", - "tag": "JSONSummary" + "summary": "Deleted the newName1 export statement" }, { "span": { @@ -1220,8 +1161,7 @@ ] } }, - "summary": "Deleted the anonymous() function export statement", - "tag": "JSONSummary" + "summary": "Deleted the anonymous() function export statement" }, { "span": { @@ -1236,8 +1176,7 @@ ] } }, - "summary": "Deleted the name2 as statement export statement", - "tag": "JSONSummary" + "summary": "Deleted the name2 as statement export statement" }, { "span": { @@ -1252,8 +1191,7 @@ ] } }, - "summary": "Deleted the 'baz' export statement", - "tag": "JSONSummary" + "summary": "Deleted the 'baz' export statement" }, { "span": { @@ -1268,8 +1206,7 @@ ] } }, - "summary": "Deleted the name7, name8, nameP from 'buzz' export statement", - "tag": "JSONSummary" + "summary": "Deleted the name7, name8, nameP from 'buzz' export statement" }, { "span": { @@ -1284,8 +1221,7 @@ ] } }, - "summary": "Deleted the import6 as name6, import7 as name7, nameB from 'fizz' export statement", - "tag": "JSONSummary" + "summary": "Deleted the import6 as name6, import7 as name7, nameB from 'fizz' export statement" } ] }, @@ -1294,9 +1230,9 @@ "filePaths": [ "export.js" ], - "sha1": "8b44c437b4f4230802f75d171dfe1e45a5131045", + "sha1": "4a8a60bc1bf98a633b4c92368a075c7990b983d7", "gitDir": "test/corpus/repos/javascript", - "sha2": "a785e114db03c32878ca52d5eb63919ab6a2157e" + "sha2": "4ffb72f4091bf1dec741647f5d9e804f0565eea6" } ,{ "testCaseDescription": "javascript-export-replacement-test", @@ -1328,8 +1264,7 @@ } ] }, - "summary": "Replaced the 'name1' identifier with the 'name4' identifier in the name4, name5, name6, nameZ export statement", - "tag": "JSONSummary" + "summary": "Replaced the 'name1' identifier with the 'name4' identifier in the name4, name5, name6, nameZ export statement" }, { "span": { @@ -1356,8 +1291,7 @@ } ] }, - "summary": "Replaced the 'name2' identifier with the 'name5' identifier in the name4, name5, name6, nameZ export statement", - "tag": "JSONSummary" + "summary": "Replaced the 'name2' identifier with the 'name5' identifier in the name4, name5, name6, nameZ export statement" }, { "span": { @@ -1384,8 +1318,7 @@ } ] }, - "summary": "Replaced the 'name3' identifier with the 'name6' identifier in the name4, name5, name6, nameZ export statement", - "tag": "JSONSummary" + "summary": "Replaced the 'name3' identifier with the 'name6' identifier in the name4, name5, name6, nameZ export statement" }, { "span": { @@ -1412,8 +1345,7 @@ } ] }, - "summary": "Replaced the 'nameN' identifier with the 'nameZ' identifier in the name4, name5, name6, nameZ export statement", - "tag": "JSONSummary" + "summary": "Replaced the 'nameN' identifier with the 'nameZ' identifier in the name4, name5, name6, nameZ export statement" }, { "span": { @@ -1428,8 +1360,7 @@ ] } }, - "summary": "Added the variable2 as name2, variable3 as name3, nameY export statement", - "tag": "JSONSummary" + "summary": "Added the variable2 as name2, variable3 as name3, nameY export statement" }, { "span": { @@ -1444,8 +1375,7 @@ ] } }, - "summary": "Added the name3, name4, nameT export statement", - "tag": "JSONSummary" + "summary": "Added the name3, name4, nameT export statement" }, { "span": { @@ -1460,8 +1390,7 @@ ] } }, - "summary": "Added the name2 = value2, name3 = value3, name4, nameO export statement", - "tag": "JSONSummary" + "summary": "Added the name2 = value2, name3 = value3, name4, nameO export statement" }, { "span": { @@ -1476,8 +1405,7 @@ ] } }, - "summary": "Added the otherNamedFunction export statement", - "tag": "JSONSummary" + "summary": "Added the otherNamedFunction export statement" }, { "span": { @@ -1492,8 +1420,7 @@ ] } }, - "summary": "Added the newName1 export statement", - "tag": "JSONSummary" + "summary": "Added the newName1 export statement" }, { "span": { @@ -1508,8 +1435,7 @@ ] } }, - "summary": "Added the anonymous() function export statement", - "tag": "JSONSummary" + "summary": "Added the anonymous() function export statement" }, { "span": { @@ -1524,8 +1450,7 @@ ] } }, - "summary": "Added the name2 as statement export statement", - "tag": "JSONSummary" + "summary": "Added the name2 as statement export statement" }, { "span": { @@ -1540,8 +1465,7 @@ ] } }, - "summary": "Added the 'baz' export statement", - "tag": "JSONSummary" + "summary": "Added the 'baz' export statement" }, { "span": { @@ -1556,8 +1480,7 @@ ] } }, - "summary": "Added the name7, name8, nameP from 'buzz' export statement", - "tag": "JSONSummary" + "summary": "Added the name7, name8, nameP from 'buzz' export statement" }, { "span": { @@ -1572,8 +1495,7 @@ ] } }, - "summary": "Added the import6 as name6, import7 as name7, nameB from 'fizz' export statement", - "tag": "JSONSummary" + "summary": "Added the import6 as name6, import7 as name7, nameB from 'fizz' export statement" }, { "span": { @@ -1588,8 +1510,7 @@ ] } }, - "summary": "Deleted the variable1 as name1, variable2 as name2, nameN export statement", - "tag": "JSONSummary" + "summary": "Deleted the variable1 as name1, variable2 as name2, nameN export statement" }, { "span": { @@ -1604,8 +1525,7 @@ ] } }, - "summary": "Deleted the name1, name2, nameN export statement", - "tag": "JSONSummary" + "summary": "Deleted the name1, name2, nameN export statement" }, { "span": { @@ -1620,8 +1540,7 @@ ] } }, - "summary": "Deleted the name1 = value1, name2 = value2, name3, nameN export statement", - "tag": "JSONSummary" + "summary": "Deleted the name1 = value1, name2 = value2, name3, nameN export statement" }, { "span": { @@ -1636,8 +1555,7 @@ ] } }, - "summary": "Deleted the namedFunction export statement", - "tag": "JSONSummary" + "summary": "Deleted the namedFunction export statement" }, { "span": { @@ -1652,8 +1570,7 @@ ] } }, - "summary": "Deleted the anonymous() function export statement", - "tag": "JSONSummary" + "summary": "Deleted the anonymous() function export statement" }, { "span": { @@ -1668,8 +1585,7 @@ ] } }, - "summary": "Deleted the name1 export statement", - "tag": "JSONSummary" + "summary": "Deleted the name1 export statement" }, { "span": { @@ -1684,8 +1600,7 @@ ] } }, - "summary": "Deleted the name1 as default export statement", - "tag": "JSONSummary" + "summary": "Deleted the name1 as default export statement" }, { "span": { @@ -1700,8 +1615,7 @@ ] } }, - "summary": "Deleted the 'foo' export statement", - "tag": "JSONSummary" + "summary": "Deleted the 'foo' export statement" }, { "span": { @@ -1716,8 +1630,7 @@ ] } }, - "summary": "Deleted the name1, name2, nameN from 'foo' export statement", - "tag": "JSONSummary" + "summary": "Deleted the name1, name2, nameN from 'foo' export statement" }, { "span": { @@ -1732,8 +1645,7 @@ ] } }, - "summary": "Deleted the import1 as name1, import2 as name2, nameN from 'bar' export statement", - "tag": "JSONSummary" + "summary": "Deleted the import1 as name1, import2 as name2, nameN from 'bar' export statement" } ] }, @@ -1742,9 +1654,9 @@ "filePaths": [ "export.js" ], - "sha1": "a785e114db03c32878ca52d5eb63919ab6a2157e", + "sha1": "4ffb72f4091bf1dec741647f5d9e804f0565eea6", "gitDir": "test/corpus/repos/javascript", - "sha2": "630f93e2ef51a3dbf92c5d9070fb2c8d4e77cbe0" + "sha2": "57d6396d5040e085e1fd7693bc553a64ca4f9820" } ,{ "testCaseDescription": "javascript-export-delete-replacement-test", @@ -1764,8 +1676,7 @@ ] } }, - "summary": "Deleted the name4, name5, name6, nameZ export statement", - "tag": "JSONSummary" + "summary": "Deleted the name4, name5, name6, nameZ export statement" }, { "span": { @@ -1780,8 +1691,7 @@ ] } }, - "summary": "Deleted the variable2 as name2, variable3 as name3, nameY export statement", - "tag": "JSONSummary" + "summary": "Deleted the variable2 as name2, variable3 as name3, nameY export statement" }, { "span": { @@ -1796,8 +1706,7 @@ ] } }, - "summary": "Deleted the name3, name4, nameT export statement", - "tag": "JSONSummary" + "summary": "Deleted the name3, name4, nameT export statement" }, { "span": { @@ -1812,8 +1721,7 @@ ] } }, - "summary": "Deleted the name2 = value2, name3 = value3, name4, nameO export statement", - "tag": "JSONSummary" + "summary": "Deleted the name2 = value2, name3 = value3, name4, nameO export statement" }, { "span": { @@ -1828,8 +1736,7 @@ ] } }, - "summary": "Deleted the otherNamedFunction export statement", - "tag": "JSONSummary" + "summary": "Deleted the otherNamedFunction export statement" }, { "span": { @@ -1844,8 +1751,7 @@ ] } }, - "summary": "Deleted the newName1 export statement", - "tag": "JSONSummary" + "summary": "Deleted the newName1 export statement" }, { "span": { @@ -1860,8 +1766,7 @@ ] } }, - "summary": "Deleted the anonymous() function export statement", - "tag": "JSONSummary" + "summary": "Deleted the anonymous() function export statement" }, { "span": { @@ -1876,8 +1781,7 @@ ] } }, - "summary": "Deleted the name2 as statement export statement", - "tag": "JSONSummary" + "summary": "Deleted the name2 as statement export statement" }, { "span": { @@ -1892,8 +1796,7 @@ ] } }, - "summary": "Deleted the 'baz' export statement", - "tag": "JSONSummary" + "summary": "Deleted the 'baz' export statement" }, { "span": { @@ -1908,8 +1811,7 @@ ] } }, - "summary": "Deleted the name7, name8, nameP from 'buzz' export statement", - "tag": "JSONSummary" + "summary": "Deleted the name7, name8, nameP from 'buzz' export statement" }, { "span": { @@ -1924,8 +1826,7 @@ ] } }, - "summary": "Deleted the import6 as name6, import7 as name7, nameB from 'fizz' export statement", - "tag": "JSONSummary" + "summary": "Deleted the import6 as name6, import7 as name7, nameB from 'fizz' export statement" }, { "span": { @@ -1940,8 +1841,7 @@ ] } }, - "summary": "Deleted the name1, name2, name3, nameN export statement", - "tag": "JSONSummary" + "summary": "Deleted the name1, name2, name3, nameN export statement" }, { "span": { @@ -1956,8 +1856,7 @@ ] } }, - "summary": "Deleted the variable1 as name1, variable2 as name2, nameN export statement", - "tag": "JSONSummary" + "summary": "Deleted the variable1 as name1, variable2 as name2, nameN export statement" }, { "span": { @@ -1972,8 +1871,7 @@ ] } }, - "summary": "Deleted the name1, name2, nameN export statement", - "tag": "JSONSummary" + "summary": "Deleted the name1, name2, nameN export statement" }, { "span": { @@ -1988,8 +1886,7 @@ ] } }, - "summary": "Deleted the name1 = value1, name2 = value2, name3, nameN export statement", - "tag": "JSONSummary" + "summary": "Deleted the name1 = value1, name2 = value2, name3, nameN export statement" }, { "span": { @@ -2004,8 +1901,7 @@ ] } }, - "summary": "Deleted the namedFunction export statement", - "tag": "JSONSummary" + "summary": "Deleted the namedFunction export statement" }, { "span": { @@ -2020,8 +1916,7 @@ ] } }, - "summary": "Deleted the anonymous() function export statement", - "tag": "JSONSummary" + "summary": "Deleted the anonymous() function export statement" }, { "span": { @@ -2036,8 +1931,7 @@ ] } }, - "summary": "Deleted the name1 export statement", - "tag": "JSONSummary" + "summary": "Deleted the name1 export statement" }, { "span": { @@ -2052,8 +1946,7 @@ ] } }, - "summary": "Deleted the name1 as default export statement", - "tag": "JSONSummary" + "summary": "Deleted the name1 as default export statement" }, { "span": { @@ -2068,8 +1961,7 @@ ] } }, - "summary": "Deleted the 'foo' export statement", - "tag": "JSONSummary" + "summary": "Deleted the 'foo' export statement" }, { "span": { @@ -2084,8 +1976,7 @@ ] } }, - "summary": "Deleted the name1, name2, nameN from 'foo' export statement", - "tag": "JSONSummary" + "summary": "Deleted the name1, name2, nameN from 'foo' export statement" }, { "span": { @@ -2100,8 +1991,7 @@ ] } }, - "summary": "Deleted the import1 as name1, import2 as name2, nameN from 'bar' export statement", - "tag": "JSONSummary" + "summary": "Deleted the import1 as name1, import2 as name2, nameN from 'bar' export statement" }, { "span": { @@ -2116,8 +2006,7 @@ ] } }, - "summary": "Added the name4, name5, name6, nameZ export statement", - "tag": "JSONSummary" + "summary": "Added the name4, name5, name6, nameZ export statement" }, { "span": { @@ -2132,8 +2021,7 @@ ] } }, - "summary": "Added the variable2 as name2, variable3 as name3, nameY export statement", - "tag": "JSONSummary" + "summary": "Added the variable2 as name2, variable3 as name3, nameY export statement" }, { "span": { @@ -2148,8 +2036,7 @@ ] } }, - "summary": "Added the name3, name4, nameT export statement", - "tag": "JSONSummary" + "summary": "Added the name3, name4, nameT export statement" }, { "span": { @@ -2164,8 +2051,7 @@ ] } }, - "summary": "Added the name2 = value2, name3 = value3, name4, nameO export statement", - "tag": "JSONSummary" + "summary": "Added the name2 = value2, name3 = value3, name4, nameO export statement" }, { "span": { @@ -2180,8 +2066,7 @@ ] } }, - "summary": "Added the otherNamedFunction export statement", - "tag": "JSONSummary" + "summary": "Added the otherNamedFunction export statement" }, { "span": { @@ -2196,8 +2081,7 @@ ] } }, - "summary": "Added the newName1 export statement", - "tag": "JSONSummary" + "summary": "Added the newName1 export statement" }, { "span": { @@ -2212,8 +2096,7 @@ ] } }, - "summary": "Added the anonymous() function export statement", - "tag": "JSONSummary" + "summary": "Added the anonymous() function export statement" }, { "span": { @@ -2228,8 +2111,7 @@ ] } }, - "summary": "Added the name2 as statement export statement", - "tag": "JSONSummary" + "summary": "Added the name2 as statement export statement" }, { "span": { @@ -2244,8 +2126,7 @@ ] } }, - "summary": "Added the 'baz' export statement", - "tag": "JSONSummary" + "summary": "Added the 'baz' export statement" }, { "span": { @@ -2260,8 +2141,7 @@ ] } }, - "summary": "Added the name7, name8, nameP from 'buzz' export statement", - "tag": "JSONSummary" + "summary": "Added the name7, name8, nameP from 'buzz' export statement" }, { "span": { @@ -2276,8 +2156,7 @@ ] } }, - "summary": "Added the import6 as name6, import7 as name7, nameB from 'fizz' export statement", - "tag": "JSONSummary" + "summary": "Added the import6 as name6, import7 as name7, nameB from 'fizz' export statement" } ] }, @@ -2286,9 +2165,9 @@ "filePaths": [ "export.js" ], - "sha1": "630f93e2ef51a3dbf92c5d9070fb2c8d4e77cbe0", + "sha1": "57d6396d5040e085e1fd7693bc553a64ca4f9820", "gitDir": "test/corpus/repos/javascript", - "sha2": "4dc68416478b18e5ab4d0cb03d1be06129ffde31" + "sha2": "228b95ad00efa68297972f82297fa541da06bcef" } ,{ "testCaseDescription": "javascript-export-delete-test", @@ -2308,8 +2187,7 @@ ] } }, - "summary": "Deleted the name1, name2, name3, nameN export statement", - "tag": "JSONSummary" + "summary": "Deleted the name1, name2, name3, nameN export statement" }, { "span": { @@ -2324,8 +2202,7 @@ ] } }, - "summary": "Deleted the variable1 as name1, variable2 as name2, nameN export statement", - "tag": "JSONSummary" + "summary": "Deleted the variable1 as name1, variable2 as name2, nameN export statement" }, { "span": { @@ -2340,8 +2217,7 @@ ] } }, - "summary": "Deleted the name1, name2, nameN export statement", - "tag": "JSONSummary" + "summary": "Deleted the name1, name2, nameN export statement" }, { "span": { @@ -2356,8 +2232,7 @@ ] } }, - "summary": "Deleted the name1 = value1, name2 = value2, name3, nameN export statement", - "tag": "JSONSummary" + "summary": "Deleted the name1 = value1, name2 = value2, name3, nameN export statement" }, { "span": { @@ -2372,8 +2247,7 @@ ] } }, - "summary": "Deleted the namedFunction export statement", - "tag": "JSONSummary" + "summary": "Deleted the namedFunction export statement" }, { "span": { @@ -2388,8 +2262,7 @@ ] } }, - "summary": "Deleted the anonymous() function export statement", - "tag": "JSONSummary" + "summary": "Deleted the anonymous() function export statement" }, { "span": { @@ -2404,8 +2277,7 @@ ] } }, - "summary": "Deleted the name1 export statement", - "tag": "JSONSummary" + "summary": "Deleted the name1 export statement" }, { "span": { @@ -2420,8 +2292,7 @@ ] } }, - "summary": "Deleted the name1 as default export statement", - "tag": "JSONSummary" + "summary": "Deleted the name1 as default export statement" }, { "span": { @@ -2436,8 +2307,7 @@ ] } }, - "summary": "Deleted the 'foo' export statement", - "tag": "JSONSummary" + "summary": "Deleted the 'foo' export statement" }, { "span": { @@ -2452,8 +2322,7 @@ ] } }, - "summary": "Deleted the name1, name2, nameN from 'foo' export statement", - "tag": "JSONSummary" + "summary": "Deleted the name1, name2, nameN from 'foo' export statement" }, { "span": { @@ -2468,8 +2337,7 @@ ] } }, - "summary": "Deleted the import1 as name1, import2 as name2, nameN from 'bar' export statement", - "tag": "JSONSummary" + "summary": "Deleted the import1 as name1, import2 as name2, nameN from 'bar' export statement" } ] }, @@ -2478,9 +2346,9 @@ "filePaths": [ "export.js" ], - "sha1": "4dc68416478b18e5ab4d0cb03d1be06129ffde31", + "sha1": "228b95ad00efa68297972f82297fa541da06bcef", "gitDir": "test/corpus/repos/javascript", - "sha2": "11d28b7ee48f99ad7e371a3ff7a3afcb482ecac5" + "sha2": "dd4e4ff10f7dda7b7bc1852747ca61eac91d9de7" } ,{ "testCaseDescription": "javascript-export-delete-rest-test", @@ -2500,8 +2368,7 @@ ] } }, - "summary": "Deleted the name4, name5, name6, nameZ export statement", - "tag": "JSONSummary" + "summary": "Deleted the name4, name5, name6, nameZ export statement" }, { "span": { @@ -2516,8 +2383,7 @@ ] } }, - "summary": "Deleted the variable2 as name2, variable3 as name3, nameY export statement", - "tag": "JSONSummary" + "summary": "Deleted the variable2 as name2, variable3 as name3, nameY export statement" }, { "span": { @@ -2532,8 +2398,7 @@ ] } }, - "summary": "Deleted the name3, name4, nameT export statement", - "tag": "JSONSummary" + "summary": "Deleted the name3, name4, nameT export statement" }, { "span": { @@ -2548,8 +2413,7 @@ ] } }, - "summary": "Deleted the name2 = value2, name3 = value3, name4, nameO export statement", - "tag": "JSONSummary" + "summary": "Deleted the name2 = value2, name3 = value3, name4, nameO export statement" }, { "span": { @@ -2564,8 +2428,7 @@ ] } }, - "summary": "Deleted the otherNamedFunction export statement", - "tag": "JSONSummary" + "summary": "Deleted the otherNamedFunction export statement" }, { "span": { @@ -2580,8 +2443,7 @@ ] } }, - "summary": "Deleted the newName1 export statement", - "tag": "JSONSummary" + "summary": "Deleted the newName1 export statement" }, { "span": { @@ -2596,8 +2458,7 @@ ] } }, - "summary": "Deleted the anonymous() function export statement", - "tag": "JSONSummary" + "summary": "Deleted the anonymous() function export statement" }, { "span": { @@ -2612,8 +2473,7 @@ ] } }, - "summary": "Deleted the name2 as statement export statement", - "tag": "JSONSummary" + "summary": "Deleted the name2 as statement export statement" }, { "span": { @@ -2628,8 +2488,7 @@ ] } }, - "summary": "Deleted the 'baz' export statement", - "tag": "JSONSummary" + "summary": "Deleted the 'baz' export statement" }, { "span": { @@ -2644,8 +2503,7 @@ ] } }, - "summary": "Deleted the name7, name8, nameP from 'buzz' export statement", - "tag": "JSONSummary" + "summary": "Deleted the name7, name8, nameP from 'buzz' export statement" }, { "span": { @@ -2660,8 +2518,7 @@ ] } }, - "summary": "Deleted the import6 as name6, import7 as name7, nameB from 'fizz' export statement", - "tag": "JSONSummary" + "summary": "Deleted the import6 as name6, import7 as name7, nameB from 'fizz' export statement" } ] }, @@ -2670,7 +2527,7 @@ "filePaths": [ "export.js" ], - "sha1": "11d28b7ee48f99ad7e371a3ff7a3afcb482ecac5", + "sha1": "dd4e4ff10f7dda7b7bc1852747ca61eac91d9de7", "gitDir": "test/corpus/repos/javascript", - "sha2": "a1ec5326a248592c7deb7a7e3b3ece00b97506bb" + "sha2": "dce5b472e5bcc43861e65b412644c7931f12d313" }] diff --git a/test/corpus/diff-summaries/javascript/nested-functions.json b/test/corpus/diff-summaries/javascript/nested-functions.json index dbe14a466..39ed1daac 100644 --- a/test/corpus/diff-summaries/javascript/nested-functions.json +++ b/test/corpus/diff-summaries/javascript/nested-functions.json @@ -16,8 +16,7 @@ ] } }, - "summary": "Added the 'parent' function", - "tag": "JSONSummary" + "summary": "Added the 'parent' function" } ] }, @@ -26,9 +25,9 @@ "filePaths": [ "nested-functions.js" ], - "sha1": "d0057ff388e8070743e2f2922cff0d9b3a2ad5de", + "sha1": "af0eafa72dc7a6795507858b2c2f9ceee614de07", "gitDir": "test/corpus/repos/javascript", - "sha2": "4ac6b2869a5665de7edc7342598666e37dd1a139" + "sha2": "71935f67586876686341a26b8cb2a41794820a6f" } ,{ "testCaseDescription": "javascript-nested-functions-replacement-insert-test", @@ -48,8 +47,7 @@ ] } }, - "summary": "Added the 'parent' function", - "tag": "JSONSummary" + "summary": "Added the 'parent' function" }, { "span": { @@ -64,8 +62,7 @@ ] } }, - "summary": "Added the 'parent' function", - "tag": "JSONSummary" + "summary": "Added the 'parent' function" } ] }, @@ -74,9 +71,9 @@ "filePaths": [ "nested-functions.js" ], - "sha1": "4ac6b2869a5665de7edc7342598666e37dd1a139", + "sha1": "71935f67586876686341a26b8cb2a41794820a6f", "gitDir": "test/corpus/repos/javascript", - "sha2": "394a62ade20d4d86615aec875b6e77b67c610af0" + "sha2": "4ea4f4876b9375f13a68d7254ad672d07b722fdf" } ,{ "testCaseDescription": "javascript-nested-functions-delete-insert-test", @@ -108,8 +105,7 @@ } ] }, - "summary": "Replaced the 'arg1' identifier with the 'arg3' identifier in the console.log(arg3) method call of the 'child' function", - "tag": "JSONSummary" + "summary": "Replaced the 'arg1' identifier with the 'arg3' identifier in the console.log(arg3) method call of the 'child' function" }, { "span": { @@ -136,8 +132,7 @@ } ] }, - "summary": "Replaced the 'arg2' identifier with the 'arg4' identifier in the console.log(arg4) method call of the 'child' function", - "tag": "JSONSummary" + "summary": "Replaced the 'arg2' identifier with the 'arg4' identifier in the console.log(arg4) method call of the 'child' function" } ] }, @@ -146,9 +141,9 @@ "filePaths": [ "nested-functions.js" ], - "sha1": "394a62ade20d4d86615aec875b6e77b67c610af0", + "sha1": "4ea4f4876b9375f13a68d7254ad672d07b722fdf", "gitDir": "test/corpus/repos/javascript", - "sha2": "7904f2aa3a357840ae49cbeb09842f4483d5b928" + "sha2": "be32782b7ddcfa08396ac01c82e30bf7b1df40e7" } ,{ "testCaseDescription": "javascript-nested-functions-replacement-test", @@ -180,8 +175,7 @@ } ] }, - "summary": "Replaced the 'arg3' identifier with the 'arg1' identifier in the console.log(arg1) method call of the 'child' function", - "tag": "JSONSummary" + "summary": "Replaced the 'arg3' identifier with the 'arg1' identifier in the console.log(arg1) method call of the 'child' function" }, { "span": { @@ -208,8 +202,7 @@ } ] }, - "summary": "Replaced the 'arg4' identifier with the 'arg2' identifier in the console.log(arg2) method call of the 'child' function", - "tag": "JSONSummary" + "summary": "Replaced the 'arg4' identifier with the 'arg2' identifier in the console.log(arg2) method call of the 'child' function" } ] }, @@ -218,9 +211,9 @@ "filePaths": [ "nested-functions.js" ], - "sha1": "7904f2aa3a357840ae49cbeb09842f4483d5b928", + "sha1": "be32782b7ddcfa08396ac01c82e30bf7b1df40e7", "gitDir": "test/corpus/repos/javascript", - "sha2": "f967788b85cc219d33d64545d8f1168ba3b43344" + "sha2": "550a976d210674327b23b298e527abe2b58dec79" } ,{ "testCaseDescription": "javascript-nested-functions-delete-replacement-test", @@ -240,8 +233,7 @@ ] } }, - "summary": "Deleted the 'parent' function", - "tag": "JSONSummary" + "summary": "Deleted the 'parent' function" }, { "span": { @@ -256,8 +248,7 @@ ] } }, - "summary": "Deleted the 'parent' function", - "tag": "JSONSummary" + "summary": "Deleted the 'parent' function" }, { "span": { @@ -272,8 +263,7 @@ ] } }, - "summary": "Added the 'parent' function", - "tag": "JSONSummary" + "summary": "Added the 'parent' function" } ] }, @@ -282,9 +272,9 @@ "filePaths": [ "nested-functions.js" ], - "sha1": "f967788b85cc219d33d64545d8f1168ba3b43344", + "sha1": "550a976d210674327b23b298e527abe2b58dec79", "gitDir": "test/corpus/repos/javascript", - "sha2": "a2a9a7ac4e107169142641d24a73e66725e9db9b" + "sha2": "cfd77d1d21ca5a1425846fe50bc154ce78ad5e6f" } ,{ "testCaseDescription": "javascript-nested-functions-delete-test", @@ -304,8 +294,7 @@ ] } }, - "summary": "Deleted the 'parent' function", - "tag": "JSONSummary" + "summary": "Deleted the 'parent' function" } ] }, @@ -314,9 +303,9 @@ "filePaths": [ "nested-functions.js" ], - "sha1": "a2a9a7ac4e107169142641d24a73e66725e9db9b", + "sha1": "cfd77d1d21ca5a1425846fe50bc154ce78ad5e6f", "gitDir": "test/corpus/repos/javascript", - "sha2": "49fdec7315d09e2ed03e0ae78e59593952d0b6d4" + "sha2": "75785663836095672233edd2495ec92237d0dbcc" } ,{ "testCaseDescription": "javascript-nested-functions-delete-rest-test", @@ -336,8 +325,7 @@ ] } }, - "summary": "Deleted the 'parent' function", - "tag": "JSONSummary" + "summary": "Deleted the 'parent' function" } ] }, @@ -346,7 +334,7 @@ "filePaths": [ "nested-functions.js" ], - "sha1": "49fdec7315d09e2ed03e0ae78e59593952d0b6d4", + "sha1": "75785663836095672233edd2495ec92237d0dbcc", "gitDir": "test/corpus/repos/javascript", - "sha2": "f49e31811346eb6451409e09e36f417aeeda390a" + "sha2": "02b2a7bb2b9b4d27a06afbe6d147ca70e6eccf1a" }] diff --git a/test/corpus/diff-summaries/javascript/null.json b/test/corpus/diff-summaries/javascript/null.json index 01061419d..5f59a978a 100644 --- a/test/corpus/diff-summaries/javascript/null.json +++ b/test/corpus/diff-summaries/javascript/null.json @@ -16,8 +16,7 @@ ] } }, - "summary": "Added the 'null' identifier", - "tag": "JSONSummary" + "summary": "Added the 'null' identifier" } ] }, @@ -26,9 +25,9 @@ "filePaths": [ "null.js" ], - "sha1": "e56eea84017cd965ac9d95cdc5c5e95a89d7d4e4", + "sha1": "0eb0a48a27bc6b8d01a210eea8cbccab5c6823f7", "gitDir": "test/corpus/repos/javascript", - "sha2": "3c20e1e7979eb2887701b29dc8774624e2a26aad" + "sha2": "921a57a0891031baea0fa0ebfc5c1270751eb7c3" } ,{ "testCaseDescription": "javascript-null-replacement-insert-test", @@ -48,8 +47,7 @@ ] } }, - "summary": "Added the 'null' return statement", - "tag": "JSONSummary" + "summary": "Added the 'null' return statement" }, { "span": { @@ -64,8 +62,7 @@ ] } }, - "summary": "Added the 'null' identifier", - "tag": "JSONSummary" + "summary": "Added the 'null' identifier" } ] }, @@ -74,9 +71,9 @@ "filePaths": [ "null.js" ], - "sha1": "3c20e1e7979eb2887701b29dc8774624e2a26aad", + "sha1": "921a57a0891031baea0fa0ebfc5c1270751eb7c3", "gitDir": "test/corpus/repos/javascript", - "sha2": "889e6f6a91e48a97e5c6f56aedecbffe19b74576" + "sha2": "1f137a24235834a5454a98078d3abb07cbdf1063" } ,{ "testCaseDescription": "javascript-null-delete-insert-test", @@ -96,8 +93,7 @@ ] } }, - "summary": "Added the 'null' identifier", - "tag": "JSONSummary" + "summary": "Added the 'null' identifier" }, { "span": { @@ -112,8 +108,7 @@ ] } }, - "summary": "Deleted the 'null' return statement", - "tag": "JSONSummary" + "summary": "Deleted the 'null' return statement" } ] }, @@ -122,9 +117,9 @@ "filePaths": [ "null.js" ], - "sha1": "889e6f6a91e48a97e5c6f56aedecbffe19b74576", + "sha1": "1f137a24235834a5454a98078d3abb07cbdf1063", "gitDir": "test/corpus/repos/javascript", - "sha2": "3b8e6eab1f7a1c5ed97eecc60850b73900c79d85" + "sha2": "1a76251123795db3deefceda4488e44d2eb80193" } ,{ "testCaseDescription": "javascript-null-replacement-test", @@ -144,8 +139,7 @@ ] } }, - "summary": "Added the 'null' return statement", - "tag": "JSONSummary" + "summary": "Added the 'null' return statement" }, { "span": { @@ -160,8 +154,7 @@ ] } }, - "summary": "Deleted the 'null' identifier", - "tag": "JSONSummary" + "summary": "Deleted the 'null' identifier" } ] }, @@ -170,9 +163,9 @@ "filePaths": [ "null.js" ], - "sha1": "3b8e6eab1f7a1c5ed97eecc60850b73900c79d85", + "sha1": "1a76251123795db3deefceda4488e44d2eb80193", "gitDir": "test/corpus/repos/javascript", - "sha2": "93e4edaad54b8a1afce14e4540858e2f48b70f1f" + "sha2": "a7adbf72c2079adee39b2dbcc46a29447cc5b452" } ,{ "testCaseDescription": "javascript-null-delete-replacement-test", @@ -192,8 +185,7 @@ ] } }, - "summary": "Deleted the 'null' return statement", - "tag": "JSONSummary" + "summary": "Deleted the 'null' return statement" }, { "span": { @@ -208,8 +200,7 @@ ] } }, - "summary": "Deleted the 'null' identifier", - "tag": "JSONSummary" + "summary": "Deleted the 'null' identifier" }, { "span": { @@ -224,8 +215,7 @@ ] } }, - "summary": "Added the 'null' return statement", - "tag": "JSONSummary" + "summary": "Added the 'null' return statement" } ] }, @@ -234,9 +224,9 @@ "filePaths": [ "null.js" ], - "sha1": "93e4edaad54b8a1afce14e4540858e2f48b70f1f", + "sha1": "a7adbf72c2079adee39b2dbcc46a29447cc5b452", "gitDir": "test/corpus/repos/javascript", - "sha2": "7401e97a5ae37d195acae99c6ca3f506ccc992db" + "sha2": "72144a33117dda641088c950e9ba56808c39d69d" } ,{ "testCaseDescription": "javascript-null-delete-test", @@ -256,8 +246,7 @@ ] } }, - "summary": "Deleted the 'null' identifier", - "tag": "JSONSummary" + "summary": "Deleted the 'null' identifier" } ] }, @@ -266,9 +255,9 @@ "filePaths": [ "null.js" ], - "sha1": "7401e97a5ae37d195acae99c6ca3f506ccc992db", + "sha1": "72144a33117dda641088c950e9ba56808c39d69d", "gitDir": "test/corpus/repos/javascript", - "sha2": "b44818542eea7ad12dd6644f2443f2df779d02d6" + "sha2": "7985243cb79eac510cc068710b58cff711ca4df7" } ,{ "testCaseDescription": "javascript-null-delete-rest-test", @@ -288,8 +277,7 @@ ] } }, - "summary": "Deleted the 'null' return statement", - "tag": "JSONSummary" + "summary": "Deleted the 'null' return statement" } ] }, @@ -298,7 +286,7 @@ "filePaths": [ "null.js" ], - "sha1": "b44818542eea7ad12dd6644f2443f2df779d02d6", + "sha1": "7985243cb79eac510cc068710b58cff711ca4df7", "gitDir": "test/corpus/repos/javascript", - "sha2": "330c4f8e410be65c3db4b801d5ca2e08094db242" + "sha2": "0785f1ff3205013dcbd5f5ca4d172e25f57b5969" }] diff --git a/test/corpus/diff-summaries/javascript/number.json b/test/corpus/diff-summaries/javascript/number.json index 3052bd17c..a4c818aea 100644 --- a/test/corpus/diff-summaries/javascript/number.json +++ b/test/corpus/diff-summaries/javascript/number.json @@ -16,8 +16,7 @@ ] } }, - "summary": "Added '101'", - "tag": "JSONSummary" + "summary": "Added '101'" } ] }, @@ -26,9 +25,9 @@ "filePaths": [ "number.js" ], - "sha1": "ca76e71a73a3fb506699ae2ab0b98373e649850c", + "sha1": "f5a546c68e4e82d0b350e3e9674659e65c938c55", "gitDir": "test/corpus/repos/javascript", - "sha2": "bca56807756346d5d207d0cf13f370ad60138dd3" + "sha2": "47960ec40f3ccbcb1153c70f228c9938575ab8ad" } ,{ "testCaseDescription": "javascript-number-replacement-insert-test", @@ -48,8 +47,7 @@ ] } }, - "summary": "Added '102'", - "tag": "JSONSummary" + "summary": "Added '102'" }, { "span": { @@ -64,8 +62,7 @@ ] } }, - "summary": "Added '101'", - "tag": "JSONSummary" + "summary": "Added '101'" } ] }, @@ -74,9 +71,9 @@ "filePaths": [ "number.js" ], - "sha1": "bca56807756346d5d207d0cf13f370ad60138dd3", + "sha1": "47960ec40f3ccbcb1153c70f228c9938575ab8ad", "gitDir": "test/corpus/repos/javascript", - "sha2": "9e399dcad95c785376aecfb4c06c940f505ed776" + "sha2": "06220f52068d26a6bcf0d23f6be481825f7923a4" } ,{ "testCaseDescription": "javascript-number-delete-insert-test", @@ -108,8 +105,7 @@ } ] }, - "summary": "Replaced '102' with '101'", - "tag": "JSONSummary" + "summary": "Replaced '102' with '101'" } ] }, @@ -118,9 +114,9 @@ "filePaths": [ "number.js" ], - "sha1": "9e399dcad95c785376aecfb4c06c940f505ed776", + "sha1": "06220f52068d26a6bcf0d23f6be481825f7923a4", "gitDir": "test/corpus/repos/javascript", - "sha2": "6333d7aab6347646f5411a86be2d868c9c19f715" + "sha2": "404abb4553e8356df1399600d506705c6c9b3ab6" } ,{ "testCaseDescription": "javascript-number-replacement-test", @@ -152,8 +148,7 @@ } ] }, - "summary": "Replaced '101' with '102'", - "tag": "JSONSummary" + "summary": "Replaced '101' with '102'" } ] }, @@ -162,9 +157,9 @@ "filePaths": [ "number.js" ], - "sha1": "6333d7aab6347646f5411a86be2d868c9c19f715", + "sha1": "404abb4553e8356df1399600d506705c6c9b3ab6", "gitDir": "test/corpus/repos/javascript", - "sha2": "cfd5fe8a3286eccda307f09fc25a504539b1cf7e" + "sha2": "7036f73a00a5222e5d9d889fe5b47ef4d77478b9" } ,{ "testCaseDescription": "javascript-number-delete-replacement-test", @@ -184,8 +179,7 @@ ] } }, - "summary": "Deleted '102'", - "tag": "JSONSummary" + "summary": "Deleted '102'" }, { "span": { @@ -200,8 +194,7 @@ ] } }, - "summary": "Deleted '101'", - "tag": "JSONSummary" + "summary": "Deleted '101'" }, { "span": { @@ -216,8 +209,7 @@ ] } }, - "summary": "Added '102'", - "tag": "JSONSummary" + "summary": "Added '102'" } ] }, @@ -226,9 +218,9 @@ "filePaths": [ "number.js" ], - "sha1": "cfd5fe8a3286eccda307f09fc25a504539b1cf7e", + "sha1": "7036f73a00a5222e5d9d889fe5b47ef4d77478b9", "gitDir": "test/corpus/repos/javascript", - "sha2": "fe9b3523d02afb88ae0bddf29eab6d2af8f135fa" + "sha2": "20984d5e617ddcbc04c1e539365976b48ba4c5e2" } ,{ "testCaseDescription": "javascript-number-delete-test", @@ -248,8 +240,7 @@ ] } }, - "summary": "Deleted '101'", - "tag": "JSONSummary" + "summary": "Deleted '101'" } ] }, @@ -258,9 +249,9 @@ "filePaths": [ "number.js" ], - "sha1": "fe9b3523d02afb88ae0bddf29eab6d2af8f135fa", + "sha1": "20984d5e617ddcbc04c1e539365976b48ba4c5e2", "gitDir": "test/corpus/repos/javascript", - "sha2": "5f00cbbdbcc8c05786b5aa95f9b909fd0f3652cf" + "sha2": "a2dd3c4c8887c73ef3ade2a1e819266cf421eca5" } ,{ "testCaseDescription": "javascript-number-delete-rest-test", @@ -280,8 +271,7 @@ ] } }, - "summary": "Deleted '102'", - "tag": "JSONSummary" + "summary": "Deleted '102'" } ] }, @@ -290,7 +280,7 @@ "filePaths": [ "number.js" ], - "sha1": "5f00cbbdbcc8c05786b5aa95f9b909fd0f3652cf", + "sha1": "a2dd3c4c8887c73ef3ade2a1e819266cf421eca5", "gitDir": "test/corpus/repos/javascript", - "sha2": "9f0cec39421594e76f56c7843f9902d1e840dcaa" + "sha2": "743cb64f1ee8a3d9f0b4ea142f1a7e8447757885" }] diff --git a/test/corpus/diff-summaries/javascript/object-with-methods.json b/test/corpus/diff-summaries/javascript/object-with-methods.json index f2e7bc5c0..fef618283 100644 --- a/test/corpus/diff-summaries/javascript/object-with-methods.json +++ b/test/corpus/diff-summaries/javascript/object-with-methods.json @@ -16,8 +16,7 @@ ] } }, - "summary": "Added the '{ add }' object", - "tag": "JSONSummary" + "summary": "Added the '{ add }' object" } ] }, @@ -26,9 +25,9 @@ "filePaths": [ "objects-with-methods.js" ], - "sha1": "f13aef7dcdfe65826b6d93b4b371afe29a12f21f", + "sha1": "9dbca3237fd8109ff6cad0cb5060962d58f10b6c", "gitDir": "test/corpus/repos/javascript", - "sha2": "96b548baab802a6e28144b588e564b28ff84ac55" + "sha2": "394896ec5ce46aa45a7fc7410424fd8682a2a70c" } ,{ "testCaseDescription": "javascript-objects-with-methods-replacement-insert-test", @@ -48,8 +47,7 @@ ] } }, - "summary": "Added the '{ subtract }' object", - "tag": "JSONSummary" + "summary": "Added the '{ subtract }' object" }, { "span": { @@ -64,8 +62,7 @@ ] } }, - "summary": "Added the '{ add }' object", - "tag": "JSONSummary" + "summary": "Added the '{ add }' object" } ] }, @@ -74,9 +71,9 @@ "filePaths": [ "objects-with-methods.js" ], - "sha1": "96b548baab802a6e28144b588e564b28ff84ac55", + "sha1": "394896ec5ce46aa45a7fc7410424fd8682a2a70c", "gitDir": "test/corpus/repos/javascript", - "sha2": "1293592160bd09b7bc12a75581a7496a70bb8f81" + "sha2": "e560db785a8c18a5f977a29c818a72926c4650ad" } ,{ "testCaseDescription": "javascript-objects-with-methods-delete-insert-test", @@ -108,8 +105,7 @@ } ] }, - "summary": "Replaced the 'subtract' identifier with the 'add' identifier in the add method", - "tag": "JSONSummary" + "summary": "Replaced the 'subtract' identifier with the 'add' identifier in the add method" } ] }, @@ -118,9 +114,9 @@ "filePaths": [ "objects-with-methods.js" ], - "sha1": "1293592160bd09b7bc12a75581a7496a70bb8f81", + "sha1": "e560db785a8c18a5f977a29c818a72926c4650ad", "gitDir": "test/corpus/repos/javascript", - "sha2": "ee09bff08bb2a4467e2d2733db38fdc35a91fa01" + "sha2": "62fd8c060f49723f91a0f405b48fe9590f519db8" } ,{ "testCaseDescription": "javascript-objects-with-methods-replacement-test", @@ -152,8 +148,7 @@ } ] }, - "summary": "Replaced the 'add' identifier with the 'subtract' identifier in the subtract method", - "tag": "JSONSummary" + "summary": "Replaced the 'add' identifier with the 'subtract' identifier in the subtract method" } ] }, @@ -162,9 +157,9 @@ "filePaths": [ "objects-with-methods.js" ], - "sha1": "ee09bff08bb2a4467e2d2733db38fdc35a91fa01", + "sha1": "62fd8c060f49723f91a0f405b48fe9590f519db8", "gitDir": "test/corpus/repos/javascript", - "sha2": "70c38b12df93c18958a2ff94145a5c1b8f64e0d1" + "sha2": "381f0d3aa4e0c53b425eb42b9f3216c07aa5c3bb" } ,{ "testCaseDescription": "javascript-objects-with-methods-delete-replacement-test", @@ -184,8 +179,7 @@ ] } }, - "summary": "Deleted the '{ subtract }' object", - "tag": "JSONSummary" + "summary": "Deleted the '{ subtract }' object" }, { "span": { @@ -200,8 +194,7 @@ ] } }, - "summary": "Deleted the '{ add }' object", - "tag": "JSONSummary" + "summary": "Deleted the '{ add }' object" }, { "span": { @@ -216,8 +209,7 @@ ] } }, - "summary": "Added the '{ subtract }' object", - "tag": "JSONSummary" + "summary": "Added the '{ subtract }' object" } ] }, @@ -226,9 +218,9 @@ "filePaths": [ "objects-with-methods.js" ], - "sha1": "70c38b12df93c18958a2ff94145a5c1b8f64e0d1", + "sha1": "381f0d3aa4e0c53b425eb42b9f3216c07aa5c3bb", "gitDir": "test/corpus/repos/javascript", - "sha2": "c9f20856166b00c740c53d34289d5bdafcfe73f8" + "sha2": "e86ec26bc3f4e22c3bef80eae7f4afbe9c3b641d" } ,{ "testCaseDescription": "javascript-objects-with-methods-delete-test", @@ -248,8 +240,7 @@ ] } }, - "summary": "Deleted the '{ add }' object", - "tag": "JSONSummary" + "summary": "Deleted the '{ add }' object" } ] }, @@ -258,9 +249,9 @@ "filePaths": [ "objects-with-methods.js" ], - "sha1": "c9f20856166b00c740c53d34289d5bdafcfe73f8", + "sha1": "e86ec26bc3f4e22c3bef80eae7f4afbe9c3b641d", "gitDir": "test/corpus/repos/javascript", - "sha2": "f8a7132e504b1bf9154a8946db3bc7a412c3e983" + "sha2": "04fb0de0a79aef0c8d6160504a7489dae59b7322" } ,{ "testCaseDescription": "javascript-objects-with-methods-delete-rest-test", @@ -280,8 +271,7 @@ ] } }, - "summary": "Deleted the '{ subtract }' object", - "tag": "JSONSummary" + "summary": "Deleted the '{ subtract }' object" } ] }, @@ -290,7 +280,7 @@ "filePaths": [ "objects-with-methods.js" ], - "sha1": "f8a7132e504b1bf9154a8946db3bc7a412c3e983", + "sha1": "04fb0de0a79aef0c8d6160504a7489dae59b7322", "gitDir": "test/corpus/repos/javascript", - "sha2": "179d020d71ae2d25e7da3fa6af1db307411db219" + "sha2": "f10a454e09922f6b39b73d7a2d1c490a2a4b6179" }] diff --git a/test/corpus/diff-summaries/javascript/object.json b/test/corpus/diff-summaries/javascript/object.json index 3222f85f1..a65123315 100644 --- a/test/corpus/diff-summaries/javascript/object.json +++ b/test/corpus/diff-summaries/javascript/object.json @@ -16,8 +16,7 @@ ] } }, - "summary": "Added the '{ \"key1\": … }' object", - "tag": "JSONSummary" + "summary": "Added the '{ \"key1\": … }' object" } ] }, @@ -26,9 +25,9 @@ "filePaths": [ "object.js" ], - "sha1": "f58cfc7947653db85574d1569f494d8b11791ad1", + "sha1": "aefeb00bb872d8308fb1f9989a0b30bee53f794e", "gitDir": "test/corpus/repos/javascript", - "sha2": "6f20c6eb26c60838e377075ef27fe3b76b98dd26" + "sha2": "8d7f9432e5eccbac5a2dce503cb6e9aabe691f64" } ,{ "testCaseDescription": "javascript-object-replacement-insert-test", @@ -48,8 +47,7 @@ ] } }, - "summary": "Added the '{ \"key1\": …, \"key2\": …, \"key3\": … }' object", - "tag": "JSONSummary" + "summary": "Added the '{ \"key1\": …, \"key2\": …, \"key3\": … }' object" }, { "span": { @@ -64,8 +62,7 @@ ] } }, - "summary": "Added the '{ \"key1\": … }' object", - "tag": "JSONSummary" + "summary": "Added the '{ \"key1\": … }' object" } ] }, @@ -74,9 +71,9 @@ "filePaths": [ "object.js" ], - "sha1": "6f20c6eb26c60838e377075ef27fe3b76b98dd26", + "sha1": "8d7f9432e5eccbac5a2dce503cb6e9aabe691f64", "gitDir": "test/corpus/repos/javascript", - "sha2": "32fccdccdc5ff2d5c4878563744f146e423e812d" + "sha2": "d4b9e799adb79bd4cc813ce5b7a528e65956b227" } ,{ "testCaseDescription": "javascript-object-delete-insert-test", @@ -96,8 +93,7 @@ ] } }, - "summary": "Deleted the '\"key2\": …' pair", - "tag": "JSONSummary" + "summary": "Deleted the '\"key2\": …' pair" }, { "span": { @@ -112,8 +108,7 @@ ] } }, - "summary": "Deleted the '\"key3\": …' pair", - "tag": "JSONSummary" + "summary": "Deleted the '\"key3\": …' pair" } ] }, @@ -122,9 +117,9 @@ "filePaths": [ "object.js" ], - "sha1": "32fccdccdc5ff2d5c4878563744f146e423e812d", + "sha1": "d4b9e799adb79bd4cc813ce5b7a528e65956b227", "gitDir": "test/corpus/repos/javascript", - "sha2": "af8db674db1087a5f2953ccfe17ba15b840f6e76" + "sha2": "181fb7d0795181379db61ff3d91e73e17a7f0176" } ,{ "testCaseDescription": "javascript-object-replacement-test", @@ -144,8 +139,7 @@ ] } }, - "summary": "Added the '\"key2\": …' pair", - "tag": "JSONSummary" + "summary": "Added the '\"key2\": …' pair" }, { "span": { @@ -160,8 +154,7 @@ ] } }, - "summary": "Added the '\"key3\": …' pair", - "tag": "JSONSummary" + "summary": "Added the '\"key3\": …' pair" } ] }, @@ -170,9 +163,9 @@ "filePaths": [ "object.js" ], - "sha1": "af8db674db1087a5f2953ccfe17ba15b840f6e76", + "sha1": "181fb7d0795181379db61ff3d91e73e17a7f0176", "gitDir": "test/corpus/repos/javascript", - "sha2": "684501429d36cd64a92cbec1c777560cad857469" + "sha2": "48b14e07a2432070ba8edc7a97b3a3f5744c4f95" } ,{ "testCaseDescription": "javascript-object-delete-replacement-test", @@ -192,8 +185,7 @@ ] } }, - "summary": "Deleted the '{ \"key1\": …, \"key2\": …, \"key3\": … }' object", - "tag": "JSONSummary" + "summary": "Deleted the '{ \"key1\": …, \"key2\": …, \"key3\": … }' object" }, { "span": { @@ -208,8 +200,7 @@ ] } }, - "summary": "Deleted the '{ \"key1\": … }' object", - "tag": "JSONSummary" + "summary": "Deleted the '{ \"key1\": … }' object" }, { "span": { @@ -224,8 +215,7 @@ ] } }, - "summary": "Added the '{ \"key1\": …, \"key2\": …, \"key3\": … }' object", - "tag": "JSONSummary" + "summary": "Added the '{ \"key1\": …, \"key2\": …, \"key3\": … }' object" } ] }, @@ -234,9 +224,9 @@ "filePaths": [ "object.js" ], - "sha1": "684501429d36cd64a92cbec1c777560cad857469", + "sha1": "48b14e07a2432070ba8edc7a97b3a3f5744c4f95", "gitDir": "test/corpus/repos/javascript", - "sha2": "b1a8ced66b7504d887f621ef64db91e3ec0d5674" + "sha2": "76e45b38000091fee41bc0a0a9f3a5cd65c5492d" } ,{ "testCaseDescription": "javascript-object-delete-test", @@ -256,8 +246,7 @@ ] } }, - "summary": "Deleted the '{ \"key1\": … }' object", - "tag": "JSONSummary" + "summary": "Deleted the '{ \"key1\": … }' object" } ] }, @@ -266,9 +255,9 @@ "filePaths": [ "object.js" ], - "sha1": "b1a8ced66b7504d887f621ef64db91e3ec0d5674", + "sha1": "76e45b38000091fee41bc0a0a9f3a5cd65c5492d", "gitDir": "test/corpus/repos/javascript", - "sha2": "02afb244f44208b28e12483be548a9b8478bb5ec" + "sha2": "2a18894fa97cf6cfb430156aa4a2e0acee543c4c" } ,{ "testCaseDescription": "javascript-object-delete-rest-test", @@ -288,8 +277,7 @@ ] } }, - "summary": "Deleted the '{ \"key1\": …, \"key2\": …, \"key3\": … }' object", - "tag": "JSONSummary" + "summary": "Deleted the '{ \"key1\": …, \"key2\": …, \"key3\": … }' object" } ] }, @@ -298,7 +286,7 @@ "filePaths": [ "object.js" ], - "sha1": "02afb244f44208b28e12483be548a9b8478bb5ec", + "sha1": "2a18894fa97cf6cfb430156aa4a2e0acee543c4c", "gitDir": "test/corpus/repos/javascript", - "sha2": "4f744373cdf308bd96fa3eec09679a7f6461d5aa" + "sha2": "0f272e863d223922521e94218a6aace378859dde" }] diff --git a/test/corpus/diff-summaries/javascript/regex.json b/test/corpus/diff-summaries/javascript/regex.json index 9101e11c4..fa918834e 100644 --- a/test/corpus/diff-summaries/javascript/regex.json +++ b/test/corpus/diff-summaries/javascript/regex.json @@ -16,8 +16,7 @@ ] } }, - "summary": "Added the '/one/g' regex", - "tag": "JSONSummary" + "summary": "Added the '/one/g' regex" } ] }, @@ -26,9 +25,9 @@ "filePaths": [ "regex.js" ], - "sha1": "8e70c5571d07dc7e882e979cd7432bc275ddb4d2", + "sha1": "af8dfb899e64bd94fbe9b1d763d771e5140c1334", "gitDir": "test/corpus/repos/javascript", - "sha2": "4c83ca78814534d5a2bc1b79686682eb348ce742" + "sha2": "5c553b5de509611f50d8cea38e7bc08712e40f84" } ,{ "testCaseDescription": "javascript-regex-replacement-insert-test", @@ -48,8 +47,7 @@ ] } }, - "summary": "Added the '/on[^/]afe/gim' regex", - "tag": "JSONSummary" + "summary": "Added the '/on[^/]afe/gim' regex" }, { "span": { @@ -64,8 +62,7 @@ ] } }, - "summary": "Added the '/one/g' regex", - "tag": "JSONSummary" + "summary": "Added the '/one/g' regex" } ] }, @@ -74,9 +71,9 @@ "filePaths": [ "regex.js" ], - "sha1": "4c83ca78814534d5a2bc1b79686682eb348ce742", + "sha1": "5c553b5de509611f50d8cea38e7bc08712e40f84", "gitDir": "test/corpus/repos/javascript", - "sha2": "7fa1b99e3e5b9c27a8d17d12149674474c053109" + "sha2": "62fa5611314d347cba6ca512031b7e98d7ed9d29" } ,{ "testCaseDescription": "javascript-regex-delete-insert-test", @@ -108,8 +105,7 @@ } ] }, - "summary": "Replaced the '/on[^/]afe/gim' regex with the '/one/g' regex", - "tag": "JSONSummary" + "summary": "Replaced the '/on[^/]afe/gim' regex with the '/one/g' regex" } ] }, @@ -118,9 +114,9 @@ "filePaths": [ "regex.js" ], - "sha1": "7fa1b99e3e5b9c27a8d17d12149674474c053109", + "sha1": "62fa5611314d347cba6ca512031b7e98d7ed9d29", "gitDir": "test/corpus/repos/javascript", - "sha2": "a4e9e5c8515b7454ffddd1033ed36517bbeddeb9" + "sha2": "405e7ab802aa3db2bac92cdb20f99bf410c57dbc" } ,{ "testCaseDescription": "javascript-regex-replacement-test", @@ -152,8 +148,7 @@ } ] }, - "summary": "Replaced the '/one/g' regex with the '/on[^/]afe/gim' regex", - "tag": "JSONSummary" + "summary": "Replaced the '/one/g' regex with the '/on[^/]afe/gim' regex" } ] }, @@ -162,9 +157,9 @@ "filePaths": [ "regex.js" ], - "sha1": "a4e9e5c8515b7454ffddd1033ed36517bbeddeb9", + "sha1": "405e7ab802aa3db2bac92cdb20f99bf410c57dbc", "gitDir": "test/corpus/repos/javascript", - "sha2": "a2874c1175ad7bf7afe04fae6708c46648ec94c9" + "sha2": "4884de88825e39386b25a8e169e393739c8bce7f" } ,{ "testCaseDescription": "javascript-regex-delete-replacement-test", @@ -184,8 +179,7 @@ ] } }, - "summary": "Deleted the '/on[^/]afe/gim' regex", - "tag": "JSONSummary" + "summary": "Deleted the '/on[^/]afe/gim' regex" }, { "span": { @@ -200,8 +194,7 @@ ] } }, - "summary": "Deleted the '/one/g' regex", - "tag": "JSONSummary" + "summary": "Deleted the '/one/g' regex" }, { "span": { @@ -216,8 +209,7 @@ ] } }, - "summary": "Added the '/on[^/]afe/gim' regex", - "tag": "JSONSummary" + "summary": "Added the '/on[^/]afe/gim' regex" } ] }, @@ -226,9 +218,9 @@ "filePaths": [ "regex.js" ], - "sha1": "a2874c1175ad7bf7afe04fae6708c46648ec94c9", + "sha1": "4884de88825e39386b25a8e169e393739c8bce7f", "gitDir": "test/corpus/repos/javascript", - "sha2": "5360c30a93987c13ebaa73a3836e2574d7f62911" + "sha2": "6c23a5a1bd35e05cad7084429ae5cca16951c4dd" } ,{ "testCaseDescription": "javascript-regex-delete-test", @@ -248,8 +240,7 @@ ] } }, - "summary": "Deleted the '/one/g' regex", - "tag": "JSONSummary" + "summary": "Deleted the '/one/g' regex" } ] }, @@ -258,9 +249,9 @@ "filePaths": [ "regex.js" ], - "sha1": "5360c30a93987c13ebaa73a3836e2574d7f62911", + "sha1": "6c23a5a1bd35e05cad7084429ae5cca16951c4dd", "gitDir": "test/corpus/repos/javascript", - "sha2": "1ae109a0e48e288712ef93815129152e6bcf1098" + "sha2": "ab5b91f92abd2e34adfba5a1819cbe1c84ec0e65" } ,{ "testCaseDescription": "javascript-regex-delete-rest-test", @@ -280,8 +271,7 @@ ] } }, - "summary": "Deleted the '/on[^/]afe/gim' regex", - "tag": "JSONSummary" + "summary": "Deleted the '/on[^/]afe/gim' regex" } ] }, @@ -290,7 +280,7 @@ "filePaths": [ "regex.js" ], - "sha1": "1ae109a0e48e288712ef93815129152e6bcf1098", + "sha1": "ab5b91f92abd2e34adfba5a1819cbe1c84ec0e65", "gitDir": "test/corpus/repos/javascript", - "sha2": "4c21f4aa629b89eee95c9af81f90075ffda6d99f" + "sha2": "b5b96ac96b0968b5b9d02ce5844f7274e13f3554" }] diff --git a/test/corpus/diff-summaries/javascript/relational-operator.json b/test/corpus/diff-summaries/javascript/relational-operator.json index 3c144ab23..3471566a6 100644 --- a/test/corpus/diff-summaries/javascript/relational-operator.json +++ b/test/corpus/diff-summaries/javascript/relational-operator.json @@ -16,8 +16,7 @@ ] } }, - "summary": "Added the 'x < y' relational operator", - "tag": "JSONSummary" + "summary": "Added the 'x < y' relational operator" } ] }, @@ -26,9 +25,9 @@ "filePaths": [ "relational-operator.js" ], - "sha1": "4acf98d6af3ab5b912b92b9b2f89018fd768fff9", + "sha1": "707d6d491b49e1d91b26dc55086e140e997fcaf4", "gitDir": "test/corpus/repos/javascript", - "sha2": "aeccebdb301fe1d07cb1644a3fbafa46388245a1" + "sha2": "916c235b3685819d8f98b4805abe2a2f863cee37" } ,{ "testCaseDescription": "javascript-relational-operator-replacement-insert-test", @@ -48,8 +47,7 @@ ] } }, - "summary": "Added the 'x <= y' relational operator", - "tag": "JSONSummary" + "summary": "Added the 'x <= y' relational operator" }, { "span": { @@ -64,8 +62,7 @@ ] } }, - "summary": "Added the 'x < y' relational operator", - "tag": "JSONSummary" + "summary": "Added the 'x < y' relational operator" } ] }, @@ -74,9 +71,9 @@ "filePaths": [ "relational-operator.js" ], - "sha1": "aeccebdb301fe1d07cb1644a3fbafa46388245a1", + "sha1": "916c235b3685819d8f98b4805abe2a2f863cee37", "gitDir": "test/corpus/repos/javascript", - "sha2": "fc6247ea42d8bdd48b5f8aee0b1719d14fd587a4" + "sha2": "fe34e80ceab52842be3fae1f56c762da6716100f" } ,{ "testCaseDescription": "javascript-relational-operator-delete-insert-test", @@ -87,9 +84,9 @@ "filePaths": [ "relational-operator.js" ], - "sha1": "fc6247ea42d8bdd48b5f8aee0b1719d14fd587a4", + "sha1": "fe34e80ceab52842be3fae1f56c762da6716100f", "gitDir": "test/corpus/repos/javascript", - "sha2": "6cba37e613638e9679495cf0e5c46a8f8388a4ba" + "sha2": "12ace7b189aaa7cd68b7735eafa5ba5af428222e" } ,{ "testCaseDescription": "javascript-relational-operator-replacement-test", @@ -100,9 +97,9 @@ "filePaths": [ "relational-operator.js" ], - "sha1": "6cba37e613638e9679495cf0e5c46a8f8388a4ba", + "sha1": "12ace7b189aaa7cd68b7735eafa5ba5af428222e", "gitDir": "test/corpus/repos/javascript", - "sha2": "1b647600a0425c2f8e412974d26807ae663e1bb8" + "sha2": "fd43a8853b4536d9b2cfb81fac73ab21a59ecb7d" } ,{ "testCaseDescription": "javascript-relational-operator-delete-replacement-test", @@ -122,8 +119,7 @@ ] } }, - "summary": "Deleted the 'x <= y' relational operator", - "tag": "JSONSummary" + "summary": "Deleted the 'x <= y' relational operator" } ] }, @@ -132,9 +128,9 @@ "filePaths": [ "relational-operator.js" ], - "sha1": "1b647600a0425c2f8e412974d26807ae663e1bb8", + "sha1": "fd43a8853b4536d9b2cfb81fac73ab21a59ecb7d", "gitDir": "test/corpus/repos/javascript", - "sha2": "1bd11093bcd52881234e023bd8edc7a8689cc180" + "sha2": "76f7572bb3b4761c61b2234b8078fc3dbb74b214" } ,{ "testCaseDescription": "javascript-relational-operator-delete-test", @@ -154,8 +150,7 @@ ] } }, - "summary": "Deleted the 'x < y' relational operator", - "tag": "JSONSummary" + "summary": "Deleted the 'x < y' relational operator" } ] }, @@ -164,9 +159,9 @@ "filePaths": [ "relational-operator.js" ], - "sha1": "1bd11093bcd52881234e023bd8edc7a8689cc180", + "sha1": "76f7572bb3b4761c61b2234b8078fc3dbb74b214", "gitDir": "test/corpus/repos/javascript", - "sha2": "60c48ce65a7d4c71ee356f684a096e6c597a2bd3" + "sha2": "4f1db5cef124c17f6473e7fca95c07ae3f84a4f9" } ,{ "testCaseDescription": "javascript-relational-operator-delete-rest-test", @@ -186,8 +181,7 @@ ] } }, - "summary": "Deleted the 'x <= y' relational operator", - "tag": "JSONSummary" + "summary": "Deleted the 'x <= y' relational operator" } ] }, @@ -196,7 +190,7 @@ "filePaths": [ "relational-operator.js" ], - "sha1": "60c48ce65a7d4c71ee356f684a096e6c597a2bd3", + "sha1": "4f1db5cef124c17f6473e7fca95c07ae3f84a4f9", "gitDir": "test/corpus/repos/javascript", - "sha2": "3c62d32d99e94fd0ece751f530c6b37fe10b1775" + "sha2": "22f62c999613fdb9f40f1fcabfd6e3900de152cb" }] diff --git a/test/corpus/diff-summaries/javascript/return-statement.json b/test/corpus/diff-summaries/javascript/return-statement.json index f640cdae1..23e667850 100644 --- a/test/corpus/diff-summaries/javascript/return-statement.json +++ b/test/corpus/diff-summaries/javascript/return-statement.json @@ -16,8 +16,7 @@ ] } }, - "summary": "Added the '5' return statement", - "tag": "JSONSummary" + "summary": "Added the '5' return statement" } ] }, @@ -26,9 +25,9 @@ "filePaths": [ "return-statement.js" ], - "sha1": "72327cf998fb96cc493108b069500422561c0d1d", + "sha1": "f6aaca47eff83aa2dd6a8ce2e41b14394977d9b3", "gitDir": "test/corpus/repos/javascript", - "sha2": "e23ed05e0a1eea7ef2688e138b8bbb0bd10fb04e" + "sha2": "524d62d049c00b51a2cea985dfb7ce08c0b6d073" } ,{ "testCaseDescription": "javascript-return-statement-replacement-insert-test", @@ -48,8 +47,7 @@ ] } }, - "summary": "Added the 'empty' return statement", - "tag": "JSONSummary" + "summary": "Added the 'empty' return statement" }, { "span": { @@ -64,8 +62,7 @@ ] } }, - "summary": "Added the '5' return statement", - "tag": "JSONSummary" + "summary": "Added the '5' return statement" } ] }, @@ -74,9 +71,9 @@ "filePaths": [ "return-statement.js" ], - "sha1": "e23ed05e0a1eea7ef2688e138b8bbb0bd10fb04e", + "sha1": "524d62d049c00b51a2cea985dfb7ce08c0b6d073", "gitDir": "test/corpus/repos/javascript", - "sha2": "4e05c84099b05aad16ab8d737c17122625fcaf49" + "sha2": "8041d77efbe04a7cd0f2ba66793621e61e0c74e3" } ,{ "testCaseDescription": "javascript-return-statement-delete-insert-test", @@ -96,8 +93,7 @@ ] } }, - "summary": "Added '5'", - "tag": "JSONSummary" + "summary": "Added '5'" } ] }, @@ -106,9 +102,9 @@ "filePaths": [ "return-statement.js" ], - "sha1": "4e05c84099b05aad16ab8d737c17122625fcaf49", + "sha1": "8041d77efbe04a7cd0f2ba66793621e61e0c74e3", "gitDir": "test/corpus/repos/javascript", - "sha2": "36f5ecef5e20cfad01f4b5612458ee7d1994fce4" + "sha2": "62102491107e2639f888bcb06ba212d8697cbbaf" } ,{ "testCaseDescription": "javascript-return-statement-replacement-test", @@ -128,8 +124,7 @@ ] } }, - "summary": "Deleted '5'", - "tag": "JSONSummary" + "summary": "Deleted '5'" } ] }, @@ -138,9 +133,9 @@ "filePaths": [ "return-statement.js" ], - "sha1": "36f5ecef5e20cfad01f4b5612458ee7d1994fce4", + "sha1": "62102491107e2639f888bcb06ba212d8697cbbaf", "gitDir": "test/corpus/repos/javascript", - "sha2": "20288d9df5198cd8c73654f4a897f0ed9a60aaa2" + "sha2": "a9ab5b797c44abed96f142adcfe1da66f0b1a5d4" } ,{ "testCaseDescription": "javascript-return-statement-delete-replacement-test", @@ -160,8 +155,7 @@ ] } }, - "summary": "Deleted the 'empty' return statement", - "tag": "JSONSummary" + "summary": "Deleted the 'empty' return statement" }, { "span": { @@ -176,8 +170,7 @@ ] } }, - "summary": "Deleted the '5' return statement", - "tag": "JSONSummary" + "summary": "Deleted the '5' return statement" }, { "span": { @@ -192,8 +185,7 @@ ] } }, - "summary": "Added the 'empty' return statement", - "tag": "JSONSummary" + "summary": "Added the 'empty' return statement" } ] }, @@ -202,9 +194,9 @@ "filePaths": [ "return-statement.js" ], - "sha1": "20288d9df5198cd8c73654f4a897f0ed9a60aaa2", + "sha1": "a9ab5b797c44abed96f142adcfe1da66f0b1a5d4", "gitDir": "test/corpus/repos/javascript", - "sha2": "af618a971319f4d867380cbf2582056e05413159" + "sha2": "86d283e41d3acb1a891c8212466478d832e7cf4f" } ,{ "testCaseDescription": "javascript-return-statement-delete-test", @@ -224,8 +216,7 @@ ] } }, - "summary": "Deleted the '5' return statement", - "tag": "JSONSummary" + "summary": "Deleted the '5' return statement" } ] }, @@ -234,9 +225,9 @@ "filePaths": [ "return-statement.js" ], - "sha1": "af618a971319f4d867380cbf2582056e05413159", + "sha1": "86d283e41d3acb1a891c8212466478d832e7cf4f", "gitDir": "test/corpus/repos/javascript", - "sha2": "5b70922a7bd2b32e0f89e752523055823e55579b" + "sha2": "5f60834d911eb278ea13e451d5c62e658f8dd7c4" } ,{ "testCaseDescription": "javascript-return-statement-delete-rest-test", @@ -256,8 +247,7 @@ ] } }, - "summary": "Deleted the 'empty' return statement", - "tag": "JSONSummary" + "summary": "Deleted the 'empty' return statement" } ] }, @@ -266,7 +256,7 @@ "filePaths": [ "return-statement.js" ], - "sha1": "5b70922a7bd2b32e0f89e752523055823e55579b", + "sha1": "5f60834d911eb278ea13e451d5c62e658f8dd7c4", "gitDir": "test/corpus/repos/javascript", - "sha2": "937643815a14601103a1ba1fcf99a82306f52ace" + "sha2": "c94930423eb6a6e61d369ac9025d969d2d2e6c1a" }] diff --git a/test/corpus/diff-summaries/javascript/string.json b/test/corpus/diff-summaries/javascript/string.json index e4ffb184c..e0d64f435 100644 --- a/test/corpus/diff-summaries/javascript/string.json +++ b/test/corpus/diff-summaries/javascript/string.json @@ -16,8 +16,7 @@ ] } }, - "summary": "Added the 'A string with \"double\" quotes' string", - "tag": "JSONSummary" + "summary": "Added the 'A string with \"double\" quotes' string" } ] }, @@ -26,9 +25,9 @@ "filePaths": [ "string.js" ], - "sha1": "b8f8704eac31cd6cb8a2d60bc6432cd69336e7ca", + "sha1": "2c57559d605a6fe81e465c7fab6c70b3ed995911", "gitDir": "test/corpus/repos/javascript", - "sha2": "1eac803d3d86b8fa340350c56d2eb7d39d6d7342" + "sha2": "63d3e81fd7d64a832830e004ea516b53f8781779" } ,{ "testCaseDescription": "javascript-string-replacement-insert-test", @@ -48,8 +47,7 @@ ] } }, - "summary": "Added the 'A different string with \"double\" quotes' string", - "tag": "JSONSummary" + "summary": "Added the 'A different string with \"double\" quotes' string" }, { "span": { @@ -64,8 +62,7 @@ ] } }, - "summary": "Added the 'A string with \"double\" quotes' string", - "tag": "JSONSummary" + "summary": "Added the 'A string with \"double\" quotes' string" } ] }, @@ -74,9 +71,9 @@ "filePaths": [ "string.js" ], - "sha1": "1eac803d3d86b8fa340350c56d2eb7d39d6d7342", + "sha1": "63d3e81fd7d64a832830e004ea516b53f8781779", "gitDir": "test/corpus/repos/javascript", - "sha2": "350a048f1d418381f48bdf81e353496de8248e0d" + "sha2": "51fa8e3cc925686b215735182f750faa5820479b" } ,{ "testCaseDescription": "javascript-string-delete-insert-test", @@ -108,8 +105,7 @@ } ] }, - "summary": "Replaced the 'A different string with \"double\" quotes' string with the 'A string with \"double\" quotes' string", - "tag": "JSONSummary" + "summary": "Replaced the 'A different string with \"double\" quotes' string with the 'A string with \"double\" quotes' string" } ] }, @@ -118,9 +114,9 @@ "filePaths": [ "string.js" ], - "sha1": "350a048f1d418381f48bdf81e353496de8248e0d", + "sha1": "51fa8e3cc925686b215735182f750faa5820479b", "gitDir": "test/corpus/repos/javascript", - "sha2": "74081edf9644d5f3e98ccf41140ebda1f2b82bc6" + "sha2": "fd50f8ac493b23fe746ee14b683b6c51af6503ec" } ,{ "testCaseDescription": "javascript-string-replacement-test", @@ -152,8 +148,7 @@ } ] }, - "summary": "Replaced the 'A string with \"double\" quotes' string with the 'A different string with \"double\" quotes' string", - "tag": "JSONSummary" + "summary": "Replaced the 'A string with \"double\" quotes' string with the 'A different string with \"double\" quotes' string" } ] }, @@ -162,9 +157,9 @@ "filePaths": [ "string.js" ], - "sha1": "74081edf9644d5f3e98ccf41140ebda1f2b82bc6", + "sha1": "fd50f8ac493b23fe746ee14b683b6c51af6503ec", "gitDir": "test/corpus/repos/javascript", - "sha2": "67dce6ee4390c8826050dbb0dcd1afb9e0c5ff38" + "sha2": "890a07342ca69ed4057e75883d8b42275147405d" } ,{ "testCaseDescription": "javascript-string-delete-replacement-test", @@ -184,8 +179,7 @@ ] } }, - "summary": "Deleted the 'A different string with \"double\" quotes' string", - "tag": "JSONSummary" + "summary": "Deleted the 'A different string with \"double\" quotes' string" }, { "span": { @@ -200,8 +194,7 @@ ] } }, - "summary": "Deleted the 'A string with \"double\" quotes' string", - "tag": "JSONSummary" + "summary": "Deleted the 'A string with \"double\" quotes' string" }, { "span": { @@ -216,8 +209,7 @@ ] } }, - "summary": "Added the 'A different string with \"double\" quotes' string", - "tag": "JSONSummary" + "summary": "Added the 'A different string with \"double\" quotes' string" } ] }, @@ -226,9 +218,9 @@ "filePaths": [ "string.js" ], - "sha1": "67dce6ee4390c8826050dbb0dcd1afb9e0c5ff38", + "sha1": "890a07342ca69ed4057e75883d8b42275147405d", "gitDir": "test/corpus/repos/javascript", - "sha2": "965488ad061223b589ff8388f3da6e539b60709a" + "sha2": "93afe1101fa2f097436cdbf596d0d8f1f8857999" } ,{ "testCaseDescription": "javascript-string-delete-test", @@ -248,8 +240,7 @@ ] } }, - "summary": "Deleted the 'A string with \"double\" quotes' string", - "tag": "JSONSummary" + "summary": "Deleted the 'A string with \"double\" quotes' string" } ] }, @@ -258,9 +249,9 @@ "filePaths": [ "string.js" ], - "sha1": "965488ad061223b589ff8388f3da6e539b60709a", + "sha1": "93afe1101fa2f097436cdbf596d0d8f1f8857999", "gitDir": "test/corpus/repos/javascript", - "sha2": "a53c564049237a36c0a19ae56698cb5587edcef9" + "sha2": "77450417d7c60d4c5e9027dbe758092098a51ad1" } ,{ "testCaseDescription": "javascript-string-delete-rest-test", @@ -280,8 +271,7 @@ ] } }, - "summary": "Deleted the 'A different string with \"double\" quotes' string", - "tag": "JSONSummary" + "summary": "Deleted the 'A different string with \"double\" quotes' string" } ] }, @@ -290,7 +280,7 @@ "filePaths": [ "string.js" ], - "sha1": "a53c564049237a36c0a19ae56698cb5587edcef9", + "sha1": "77450417d7c60d4c5e9027dbe758092098a51ad1", "gitDir": "test/corpus/repos/javascript", - "sha2": "ba4af0c2eb2e6c815e957def7e452a8f06765f94" + "sha2": "2bdf24d58c9431fd69cc73d80180388bb579a170" }] diff --git a/test/corpus/diff-summaries/javascript/subscript-access-assignment.json b/test/corpus/diff-summaries/javascript/subscript-access-assignment.json index 750dcb2b5..ea0f1a079 100644 --- a/test/corpus/diff-summaries/javascript/subscript-access-assignment.json +++ b/test/corpus/diff-summaries/javascript/subscript-access-assignment.json @@ -16,8 +16,7 @@ ] } }, - "summary": "Added the 'y[\"x\"]' assignment", - "tag": "JSONSummary" + "summary": "Added the 'y[\"x\"]' assignment" } ] }, @@ -26,9 +25,9 @@ "filePaths": [ "subscript-access-assignment.js" ], - "sha1": "017dd08471859c04fa5958753782e80f6b974bb4", + "sha1": "64a9a65e90cf48c435d6c1c46b80cf7935b26413", "gitDir": "test/corpus/repos/javascript", - "sha2": "cc4a86eba8cdee2e08e6cff2030c5d2b7e677d8b" + "sha2": "0148ee834e361c93f645aa32ac05516803f56d3d" } ,{ "testCaseDescription": "javascript-subscript-access-assignment-replacement-insert-test", @@ -48,8 +47,7 @@ ] } }, - "summary": "Added the 'y[\"x\"]' assignment", - "tag": "JSONSummary" + "summary": "Added the 'y[\"x\"]' assignment" }, { "span": { @@ -64,8 +62,7 @@ ] } }, - "summary": "Added the 'y[\"x\"]' assignment", - "tag": "JSONSummary" + "summary": "Added the 'y[\"x\"]' assignment" } ] }, @@ -74,9 +71,9 @@ "filePaths": [ "subscript-access-assignment.js" ], - "sha1": "cc4a86eba8cdee2e08e6cff2030c5d2b7e677d8b", + "sha1": "0148ee834e361c93f645aa32ac05516803f56d3d", "gitDir": "test/corpus/repos/javascript", - "sha2": "3705016f2c59cf2a7362e51f25a691619e63b0ef" + "sha2": "bcdee486f71016fc693985b4f6a5d0d472e8c5ff" } ,{ "testCaseDescription": "javascript-subscript-access-assignment-delete-insert-test", @@ -108,8 +105,7 @@ } ] }, - "summary": "Replaced '1' with '0' in an assignment to y[\"x\"]", - "tag": "JSONSummary" + "summary": "Replaced '1' with '0' in an assignment to y[\"x\"]" } ] }, @@ -118,9 +114,9 @@ "filePaths": [ "subscript-access-assignment.js" ], - "sha1": "3705016f2c59cf2a7362e51f25a691619e63b0ef", + "sha1": "bcdee486f71016fc693985b4f6a5d0d472e8c5ff", "gitDir": "test/corpus/repos/javascript", - "sha2": "fd2d02ddfc93fb1668a6c5baf512b71ef369ea18" + "sha2": "7f3bc8ffdd75c0bfba679d28e3d16105a50eb9f8" } ,{ "testCaseDescription": "javascript-subscript-access-assignment-replacement-test", @@ -152,8 +148,7 @@ } ] }, - "summary": "Replaced '0' with '1' in an assignment to y[\"x\"]", - "tag": "JSONSummary" + "summary": "Replaced '0' with '1' in an assignment to y[\"x\"]" } ] }, @@ -162,9 +157,9 @@ "filePaths": [ "subscript-access-assignment.js" ], - "sha1": "fd2d02ddfc93fb1668a6c5baf512b71ef369ea18", + "sha1": "7f3bc8ffdd75c0bfba679d28e3d16105a50eb9f8", "gitDir": "test/corpus/repos/javascript", - "sha2": "e4665c506aad21e4dcc6a8b7062581abe3bf62a0" + "sha2": "c3aff9f350cd0e8260f4a384b249bf7a94e7acb1" } ,{ "testCaseDescription": "javascript-subscript-access-assignment-delete-replacement-test", @@ -184,8 +179,7 @@ ] } }, - "summary": "Deleted the 'y[\"x\"]' assignment", - "tag": "JSONSummary" + "summary": "Deleted the 'y[\"x\"]' assignment" }, { "span": { @@ -200,8 +194,7 @@ ] } }, - "summary": "Deleted the 'y[\"x\"]' assignment", - "tag": "JSONSummary" + "summary": "Deleted the 'y[\"x\"]' assignment" }, { "span": { @@ -216,8 +209,7 @@ ] } }, - "summary": "Added the 'y[\"x\"]' assignment", - "tag": "JSONSummary" + "summary": "Added the 'y[\"x\"]' assignment" } ] }, @@ -226,9 +218,9 @@ "filePaths": [ "subscript-access-assignment.js" ], - "sha1": "e4665c506aad21e4dcc6a8b7062581abe3bf62a0", + "sha1": "c3aff9f350cd0e8260f4a384b249bf7a94e7acb1", "gitDir": "test/corpus/repos/javascript", - "sha2": "6bfa39fdfcb071bc8fb75a5fd05494f69a160100" + "sha2": "f31563441a2e6ad63ed5a261a4f7be1a11b82eac" } ,{ "testCaseDescription": "javascript-subscript-access-assignment-delete-test", @@ -248,8 +240,7 @@ ] } }, - "summary": "Deleted the 'y[\"x\"]' assignment", - "tag": "JSONSummary" + "summary": "Deleted the 'y[\"x\"]' assignment" } ] }, @@ -258,9 +249,9 @@ "filePaths": [ "subscript-access-assignment.js" ], - "sha1": "6bfa39fdfcb071bc8fb75a5fd05494f69a160100", + "sha1": "f31563441a2e6ad63ed5a261a4f7be1a11b82eac", "gitDir": "test/corpus/repos/javascript", - "sha2": "5d2d00d3e46ea666a3a9b5c03696bd67cf6c731e" + "sha2": "6d226d202513c5c50d0ceb3f3fd85f8d303fcf74" } ,{ "testCaseDescription": "javascript-subscript-access-assignment-delete-rest-test", @@ -280,8 +271,7 @@ ] } }, - "summary": "Deleted the 'y[\"x\"]' assignment", - "tag": "JSONSummary" + "summary": "Deleted the 'y[\"x\"]' assignment" } ] }, @@ -290,7 +280,7 @@ "filePaths": [ "subscript-access-assignment.js" ], - "sha1": "5d2d00d3e46ea666a3a9b5c03696bd67cf6c731e", + "sha1": "6d226d202513c5c50d0ceb3f3fd85f8d303fcf74", "gitDir": "test/corpus/repos/javascript", - "sha2": "7bc80d411bdd18724ae9d923e005035511ffc430" + "sha2": "acc75ec053faa10bfebdd149cbf41d414f3089fb" }] diff --git a/test/corpus/diff-summaries/javascript/subscript-access-string.json b/test/corpus/diff-summaries/javascript/subscript-access-string.json index f90a687be..f04e218c8 100644 --- a/test/corpus/diff-summaries/javascript/subscript-access-string.json +++ b/test/corpus/diff-summaries/javascript/subscript-access-string.json @@ -16,8 +16,7 @@ ] } }, - "summary": "Added the 'x[\"some-string\"]' subscript access", - "tag": "JSONSummary" + "summary": "Added the 'x[\"some-string\"]' subscript access" } ] }, @@ -26,9 +25,9 @@ "filePaths": [ "subscript-access-string.js" ], - "sha1": "055309ae7840b70d0f2d4d43ae7d46457f14ab9d", + "sha1": "5fb1a0314101669d4cfd005c86d42e20fe86d7c9", "gitDir": "test/corpus/repos/javascript", - "sha2": "3f459d64b1020d0ca06e2f100b75f9f73c494a47" + "sha2": "fa043ac413c9b7b75a82168891b6d00eee678b92" } ,{ "testCaseDescription": "javascript-subscript-access-string-replacement-insert-test", @@ -48,8 +47,7 @@ ] } }, - "summary": "Added the 'x[\"some-other-string\"]' subscript access", - "tag": "JSONSummary" + "summary": "Added the 'x[\"some-other-string\"]' subscript access" }, { "span": { @@ -64,8 +62,7 @@ ] } }, - "summary": "Added the 'x[\"some-string\"]' subscript access", - "tag": "JSONSummary" + "summary": "Added the 'x[\"some-string\"]' subscript access" } ] }, @@ -74,9 +71,9 @@ "filePaths": [ "subscript-access-string.js" ], - "sha1": "3f459d64b1020d0ca06e2f100b75f9f73c494a47", + "sha1": "fa043ac413c9b7b75a82168891b6d00eee678b92", "gitDir": "test/corpus/repos/javascript", - "sha2": "01f74ece7b9229fc2dfd67d4d81dd7fa0c48b6ca" + "sha2": "08a7b1b79627d5ecf2f6c2a44d1c2096d659e096" } ,{ "testCaseDescription": "javascript-subscript-access-string-delete-insert-test", @@ -108,8 +105,7 @@ } ] }, - "summary": "Replaced the \"some-other-string\" string with the \"some-string\" string in the x[\"some-string\"] subscript access", - "tag": "JSONSummary" + "summary": "Replaced the \"some-other-string\" string with the \"some-string\" string in the x[\"some-string\"] subscript access" } ] }, @@ -118,9 +114,9 @@ "filePaths": [ "subscript-access-string.js" ], - "sha1": "01f74ece7b9229fc2dfd67d4d81dd7fa0c48b6ca", + "sha1": "08a7b1b79627d5ecf2f6c2a44d1c2096d659e096", "gitDir": "test/corpus/repos/javascript", - "sha2": "44e5b5a6ab3131846486eea2f5c9b6fd07cd78f9" + "sha2": "f95d1cff9be9bd90156ccd975f57021c1f8eefaa" } ,{ "testCaseDescription": "javascript-subscript-access-string-replacement-test", @@ -152,8 +148,7 @@ } ] }, - "summary": "Replaced the \"some-string\" string with the \"some-other-string\" string in the x[\"some-other-string\"] subscript access", - "tag": "JSONSummary" + "summary": "Replaced the \"some-string\" string with the \"some-other-string\" string in the x[\"some-other-string\"] subscript access" } ] }, @@ -162,9 +157,9 @@ "filePaths": [ "subscript-access-string.js" ], - "sha1": "44e5b5a6ab3131846486eea2f5c9b6fd07cd78f9", + "sha1": "f95d1cff9be9bd90156ccd975f57021c1f8eefaa", "gitDir": "test/corpus/repos/javascript", - "sha2": "c0709672fa207a2ceffe8c206b7bd7fa62f47f31" + "sha2": "b9a70f9be8d0f10a65ec1c067062f2cb065a7f4a" } ,{ "testCaseDescription": "javascript-subscript-access-string-delete-replacement-test", @@ -184,8 +179,7 @@ ] } }, - "summary": "Deleted the 'x[\"some-other-string\"]' subscript access", - "tag": "JSONSummary" + "summary": "Deleted the 'x[\"some-other-string\"]' subscript access" }, { "span": { @@ -200,8 +194,7 @@ ] } }, - "summary": "Deleted the 'x[\"some-string\"]' subscript access", - "tag": "JSONSummary" + "summary": "Deleted the 'x[\"some-string\"]' subscript access" }, { "span": { @@ -216,8 +209,7 @@ ] } }, - "summary": "Added the 'x[\"some-other-string\"]' subscript access", - "tag": "JSONSummary" + "summary": "Added the 'x[\"some-other-string\"]' subscript access" } ] }, @@ -226,9 +218,9 @@ "filePaths": [ "subscript-access-string.js" ], - "sha1": "c0709672fa207a2ceffe8c206b7bd7fa62f47f31", + "sha1": "b9a70f9be8d0f10a65ec1c067062f2cb065a7f4a", "gitDir": "test/corpus/repos/javascript", - "sha2": "1b7e1b1f1f8ceb744c0dd33891f3450b959244ec" + "sha2": "ea9a6faa38a6630a573c055d81b574d5c9bbc033" } ,{ "testCaseDescription": "javascript-subscript-access-string-delete-test", @@ -248,8 +240,7 @@ ] } }, - "summary": "Deleted the 'x[\"some-string\"]' subscript access", - "tag": "JSONSummary" + "summary": "Deleted the 'x[\"some-string\"]' subscript access" } ] }, @@ -258,9 +249,9 @@ "filePaths": [ "subscript-access-string.js" ], - "sha1": "1b7e1b1f1f8ceb744c0dd33891f3450b959244ec", + "sha1": "ea9a6faa38a6630a573c055d81b574d5c9bbc033", "gitDir": "test/corpus/repos/javascript", - "sha2": "e20ee48f0142390f566a98632a95bd2b359d6ee9" + "sha2": "f49f652c070f4bf8a8a3950fe588b2e0039e5cc4" } ,{ "testCaseDescription": "javascript-subscript-access-string-delete-rest-test", @@ -280,8 +271,7 @@ ] } }, - "summary": "Deleted the 'x[\"some-other-string\"]' subscript access", - "tag": "JSONSummary" + "summary": "Deleted the 'x[\"some-other-string\"]' subscript access" } ] }, @@ -290,7 +280,7 @@ "filePaths": [ "subscript-access-string.js" ], - "sha1": "e20ee48f0142390f566a98632a95bd2b359d6ee9", + "sha1": "f49f652c070f4bf8a8a3950fe588b2e0039e5cc4", "gitDir": "test/corpus/repos/javascript", - "sha2": "14ac6caff6e171f4fac4e19d763b702382e888f0" + "sha2": "b934ce54bbf5097cc87a64591e51df2b0139a940" }] diff --git a/test/corpus/diff-summaries/javascript/subscript-access-variable.json b/test/corpus/diff-summaries/javascript/subscript-access-variable.json index 5f19bce25..fc22498b5 100644 --- a/test/corpus/diff-summaries/javascript/subscript-access-variable.json +++ b/test/corpus/diff-summaries/javascript/subscript-access-variable.json @@ -16,8 +16,7 @@ ] } }, - "summary": "Added the 'x[someVariable]' subscript access", - "tag": "JSONSummary" + "summary": "Added the 'x[someVariable]' subscript access" } ] }, @@ -26,9 +25,9 @@ "filePaths": [ "subscript-access-variable.js" ], - "sha1": "df2335a693daaeb905d9cefae31682611df78425", + "sha1": "35771d9839083e28344a82ab572b45449680ab65", "gitDir": "test/corpus/repos/javascript", - "sha2": "52bab682e3cf604bcd61e8caaa224d7ef8a86e68" + "sha2": "dfbfa45cf724b9a16226e8d0410e91ccb69cbbe3" } ,{ "testCaseDescription": "javascript-subscript-access-variable-replacement-insert-test", @@ -48,8 +47,7 @@ ] } }, - "summary": "Added the 'x[someOtherVariable]' subscript access", - "tag": "JSONSummary" + "summary": "Added the 'x[someOtherVariable]' subscript access" }, { "span": { @@ -64,8 +62,7 @@ ] } }, - "summary": "Added the 'x[someVariable]' subscript access", - "tag": "JSONSummary" + "summary": "Added the 'x[someVariable]' subscript access" } ] }, @@ -74,9 +71,9 @@ "filePaths": [ "subscript-access-variable.js" ], - "sha1": "52bab682e3cf604bcd61e8caaa224d7ef8a86e68", + "sha1": "dfbfa45cf724b9a16226e8d0410e91ccb69cbbe3", "gitDir": "test/corpus/repos/javascript", - "sha2": "01e3f51dfa5b83ed2f37105cc7360e3eca5316a6" + "sha2": "c853b9ef85feb46622a4d7a24542a26e1ceea602" } ,{ "testCaseDescription": "javascript-subscript-access-variable-delete-insert-test", @@ -108,8 +105,7 @@ } ] }, - "summary": "Replaced the 'someOtherVariable' identifier with the 'someVariable' identifier in the x[someVariable] subscript access", - "tag": "JSONSummary" + "summary": "Replaced the 'someOtherVariable' identifier with the 'someVariable' identifier in the x[someVariable] subscript access" } ] }, @@ -118,9 +114,9 @@ "filePaths": [ "subscript-access-variable.js" ], - "sha1": "01e3f51dfa5b83ed2f37105cc7360e3eca5316a6", + "sha1": "c853b9ef85feb46622a4d7a24542a26e1ceea602", "gitDir": "test/corpus/repos/javascript", - "sha2": "38aec4dba28e276cc9993f4e333b8f3a5083ccdc" + "sha2": "8c7964617fa9ed63c35663da54e463e1cedebc87" } ,{ "testCaseDescription": "javascript-subscript-access-variable-replacement-test", @@ -152,8 +148,7 @@ } ] }, - "summary": "Replaced the 'someVariable' identifier with the 'someOtherVariable' identifier in the x[someOtherVariable] subscript access", - "tag": "JSONSummary" + "summary": "Replaced the 'someVariable' identifier with the 'someOtherVariable' identifier in the x[someOtherVariable] subscript access" } ] }, @@ -162,9 +157,9 @@ "filePaths": [ "subscript-access-variable.js" ], - "sha1": "38aec4dba28e276cc9993f4e333b8f3a5083ccdc", + "sha1": "8c7964617fa9ed63c35663da54e463e1cedebc87", "gitDir": "test/corpus/repos/javascript", - "sha2": "8117127e7003788daf170172249a9e3aa7017d65" + "sha2": "1743980c0a2d957e974333f4a7fe7be2aee103b4" } ,{ "testCaseDescription": "javascript-subscript-access-variable-delete-replacement-test", @@ -184,8 +179,7 @@ ] } }, - "summary": "Deleted the 'x[someOtherVariable]' subscript access", - "tag": "JSONSummary" + "summary": "Deleted the 'x[someOtherVariable]' subscript access" }, { "span": { @@ -200,8 +194,7 @@ ] } }, - "summary": "Deleted the 'x[someVariable]' subscript access", - "tag": "JSONSummary" + "summary": "Deleted the 'x[someVariable]' subscript access" }, { "span": { @@ -216,8 +209,7 @@ ] } }, - "summary": "Added the 'x[someOtherVariable]' subscript access", - "tag": "JSONSummary" + "summary": "Added the 'x[someOtherVariable]' subscript access" } ] }, @@ -226,9 +218,9 @@ "filePaths": [ "subscript-access-variable.js" ], - "sha1": "8117127e7003788daf170172249a9e3aa7017d65", + "sha1": "1743980c0a2d957e974333f4a7fe7be2aee103b4", "gitDir": "test/corpus/repos/javascript", - "sha2": "797904d3a94beb332c011c660c738e2715d89065" + "sha2": "cfd54e85a90ff88f76612bf060a9cc2f917f5648" } ,{ "testCaseDescription": "javascript-subscript-access-variable-delete-test", @@ -248,8 +240,7 @@ ] } }, - "summary": "Deleted the 'x[someVariable]' subscript access", - "tag": "JSONSummary" + "summary": "Deleted the 'x[someVariable]' subscript access" } ] }, @@ -258,9 +249,9 @@ "filePaths": [ "subscript-access-variable.js" ], - "sha1": "797904d3a94beb332c011c660c738e2715d89065", + "sha1": "cfd54e85a90ff88f76612bf060a9cc2f917f5648", "gitDir": "test/corpus/repos/javascript", - "sha2": "f20978a2f5d640425cabb0269559ffc12d458b10" + "sha2": "58c32b6f0cb4ee41b2486ed0c4a08c4b7bb91d5b" } ,{ "testCaseDescription": "javascript-subscript-access-variable-delete-rest-test", @@ -280,8 +271,7 @@ ] } }, - "summary": "Deleted the 'x[someOtherVariable]' subscript access", - "tag": "JSONSummary" + "summary": "Deleted the 'x[someOtherVariable]' subscript access" } ] }, @@ -290,7 +280,7 @@ "filePaths": [ "subscript-access-variable.js" ], - "sha1": "f20978a2f5d640425cabb0269559ffc12d458b10", + "sha1": "58c32b6f0cb4ee41b2486ed0c4a08c4b7bb91d5b", "gitDir": "test/corpus/repos/javascript", - "sha2": "0bc2b022a5e932ce5bf00c8ebc18b4facc9c1920" + "sha2": "07ef5da0087fbbef26cc63b4629a9c05e919a68b" }] diff --git a/test/corpus/diff-summaries/javascript/switch-statement.json b/test/corpus/diff-summaries/javascript/switch-statement.json index 2991969d1..3191eaa76 100644 --- a/test/corpus/diff-summaries/javascript/switch-statement.json +++ b/test/corpus/diff-summaries/javascript/switch-statement.json @@ -16,8 +16,7 @@ ] } }, - "summary": "Added the '1' switch statement", - "tag": "JSONSummary" + "summary": "Added the '1' switch statement" } ] }, @@ -26,9 +25,9 @@ "filePaths": [ "switch-statement.js" ], - "sha1": "185540018fb2ec8f53780e07b2dfbf4a2f1236e3", + "sha1": "d30e43ec820b535d256a20ed0964fba95c8764b3", "gitDir": "test/corpus/repos/javascript", - "sha2": "e7f419c35bf0a7ee9762ed82ccc1f2186c76ae73" + "sha2": "6f28b051550ecf618c5ec1fc4109a47787a4da9c" } ,{ "testCaseDescription": "javascript-switch-statement-replacement-insert-test", @@ -48,8 +47,7 @@ ] } }, - "summary": "Added the '2' switch statement", - "tag": "JSONSummary" + "summary": "Added the '2' switch statement" }, { "span": { @@ -64,8 +62,7 @@ ] } }, - "summary": "Added the '1' switch statement", - "tag": "JSONSummary" + "summary": "Added the '1' switch statement" } ] }, @@ -74,9 +71,9 @@ "filePaths": [ "switch-statement.js" ], - "sha1": "e7f419c35bf0a7ee9762ed82ccc1f2186c76ae73", + "sha1": "6f28b051550ecf618c5ec1fc4109a47787a4da9c", "gitDir": "test/corpus/repos/javascript", - "sha2": "d64d1ff1bfae7d772398045eb64f6af967f9e873" + "sha2": "c7bbc680850439b171c5c39a1dbb8bf3f4b258f1" } ,{ "testCaseDescription": "javascript-switch-statement-delete-insert-test", @@ -108,8 +105,7 @@ } ] }, - "summary": "Replaced '2' with '1'", - "tag": "JSONSummary" + "summary": "Replaced '2' with '1'" }, { "span": { @@ -136,8 +132,7 @@ } ] }, - "summary": "Replaced '2' with '1'", - "tag": "JSONSummary" + "summary": "Replaced '2' with '1'" } ] }, @@ -146,9 +141,9 @@ "filePaths": [ "switch-statement.js" ], - "sha1": "d64d1ff1bfae7d772398045eb64f6af967f9e873", + "sha1": "c7bbc680850439b171c5c39a1dbb8bf3f4b258f1", "gitDir": "test/corpus/repos/javascript", - "sha2": "6115f065ab997428c6bccc9e5127b10bc064878b" + "sha2": "e1abf04722dcc2abc2e741e80c3d9c5bbaf94ab6" } ,{ "testCaseDescription": "javascript-switch-statement-replacement-test", @@ -180,8 +175,7 @@ } ] }, - "summary": "Replaced '1' with '2'", - "tag": "JSONSummary" + "summary": "Replaced '1' with '2'" }, { "span": { @@ -208,8 +202,7 @@ } ] }, - "summary": "Replaced '1' with '2'", - "tag": "JSONSummary" + "summary": "Replaced '1' with '2'" } ] }, @@ -218,9 +211,9 @@ "filePaths": [ "switch-statement.js" ], - "sha1": "6115f065ab997428c6bccc9e5127b10bc064878b", + "sha1": "e1abf04722dcc2abc2e741e80c3d9c5bbaf94ab6", "gitDir": "test/corpus/repos/javascript", - "sha2": "fe697bb20735d00750474bb1c1d11cf7de7d5584" + "sha2": "f3d3fb5a9daeccf22d32dbcf79e3e6db7e00ac2e" } ,{ "testCaseDescription": "javascript-switch-statement-delete-replacement-test", @@ -240,8 +233,7 @@ ] } }, - "summary": "Deleted the '2' switch statement", - "tag": "JSONSummary" + "summary": "Deleted the '2' switch statement" }, { "span": { @@ -256,8 +248,7 @@ ] } }, - "summary": "Deleted the '1' switch statement", - "tag": "JSONSummary" + "summary": "Deleted the '1' switch statement" }, { "span": { @@ -272,8 +263,7 @@ ] } }, - "summary": "Added the '2' switch statement", - "tag": "JSONSummary" + "summary": "Added the '2' switch statement" } ] }, @@ -282,9 +272,9 @@ "filePaths": [ "switch-statement.js" ], - "sha1": "fe697bb20735d00750474bb1c1d11cf7de7d5584", + "sha1": "f3d3fb5a9daeccf22d32dbcf79e3e6db7e00ac2e", "gitDir": "test/corpus/repos/javascript", - "sha2": "a526798e6a2479b18ad0c9e44f6e9ccc22123a0d" + "sha2": "033f48b1db9de57690d1e8008aabb6435eb33732" } ,{ "testCaseDescription": "javascript-switch-statement-delete-test", @@ -304,8 +294,7 @@ ] } }, - "summary": "Deleted the '1' switch statement", - "tag": "JSONSummary" + "summary": "Deleted the '1' switch statement" } ] }, @@ -314,9 +303,9 @@ "filePaths": [ "switch-statement.js" ], - "sha1": "a526798e6a2479b18ad0c9e44f6e9ccc22123a0d", + "sha1": "033f48b1db9de57690d1e8008aabb6435eb33732", "gitDir": "test/corpus/repos/javascript", - "sha2": "6b094744d7e483c03d2bf75a86ae72d45045fe5a" + "sha2": "cf1d8915d86aa7b40cc64d3a1b48e4633a034465" } ,{ "testCaseDescription": "javascript-switch-statement-delete-rest-test", @@ -336,8 +325,7 @@ ] } }, - "summary": "Deleted the '2' switch statement", - "tag": "JSONSummary" + "summary": "Deleted the '2' switch statement" } ] }, @@ -346,7 +334,7 @@ "filePaths": [ "switch-statement.js" ], - "sha1": "6b094744d7e483c03d2bf75a86ae72d45045fe5a", + "sha1": "cf1d8915d86aa7b40cc64d3a1b48e4633a034465", "gitDir": "test/corpus/repos/javascript", - "sha2": "70cb9ad4daaaabe8cba879105f1fa77141f6fa7c" + "sha2": "e34cec33423018aab0fa290f745d2dcb89c93f0f" }] diff --git a/test/corpus/diff-summaries/javascript/template-string.json b/test/corpus/diff-summaries/javascript/template-string.json index c2a1514e6..ec22725e1 100644 --- a/test/corpus/diff-summaries/javascript/template-string.json +++ b/test/corpus/diff-summaries/javascript/template-string.json @@ -16,8 +16,7 @@ ] } }, - "summary": "Added the '`one line`' template string", - "tag": "JSONSummary" + "summary": "Added the '`one line`' template string" } ] }, @@ -26,9 +25,9 @@ "filePaths": [ "template-string.js" ], - "sha1": "d4e864dd49194a81638843e841ec695be0760a6d", + "sha1": "eac947afc7bc887c4b69523c4a6f77983a183edb", "gitDir": "test/corpus/repos/javascript", - "sha2": "0d94ff9667630ffc860f5cb5333f5f26852ae555" + "sha2": "950c2afcd03ac3b200b4f8b9a9aec3817648b04b" } ,{ "testCaseDescription": "javascript-template-string-replacement-insert-test", @@ -48,8 +47,7 @@ ] } }, - "summary": "Added the '`multi line`' template string", - "tag": "JSONSummary" + "summary": "Added the '`multi line`' template string" }, { "span": { @@ -64,8 +62,7 @@ ] } }, - "summary": "Added the '`one line`' template string", - "tag": "JSONSummary" + "summary": "Added the '`one line`' template string" } ] }, @@ -74,9 +71,9 @@ "filePaths": [ "template-string.js" ], - "sha1": "0d94ff9667630ffc860f5cb5333f5f26852ae555", + "sha1": "950c2afcd03ac3b200b4f8b9a9aec3817648b04b", "gitDir": "test/corpus/repos/javascript", - "sha2": "72faa91275c8937b1126145609c84a63ab46fbae" + "sha2": "accc809e8ce1122d8b6151774c1fd769309c8e0f" } ,{ "testCaseDescription": "javascript-template-string-delete-insert-test", @@ -108,8 +105,7 @@ } ] }, - "summary": "Replaced the '`multi line`' template string with the '`one line`' template string", - "tag": "JSONSummary" + "summary": "Replaced the '`multi line`' template string with the '`one line`' template string" } ] }, @@ -118,9 +114,9 @@ "filePaths": [ "template-string.js" ], - "sha1": "72faa91275c8937b1126145609c84a63ab46fbae", + "sha1": "accc809e8ce1122d8b6151774c1fd769309c8e0f", "gitDir": "test/corpus/repos/javascript", - "sha2": "db2725ffb5682a26cd55df80bd00aec08cbd0a43" + "sha2": "8737d021e9a9a63b61b17a1a18feb0e56dd25833" } ,{ "testCaseDescription": "javascript-template-string-replacement-test", @@ -152,8 +148,7 @@ } ] }, - "summary": "Replaced the '`one line`' template string with the '`multi line`' template string", - "tag": "JSONSummary" + "summary": "Replaced the '`one line`' template string with the '`multi line`' template string" } ] }, @@ -162,9 +157,9 @@ "filePaths": [ "template-string.js" ], - "sha1": "db2725ffb5682a26cd55df80bd00aec08cbd0a43", + "sha1": "8737d021e9a9a63b61b17a1a18feb0e56dd25833", "gitDir": "test/corpus/repos/javascript", - "sha2": "90298bc75cf5d9c6227abf73fad97faae4e47c59" + "sha2": "7b2f1a9735c2c7e49481be1f7ca76a4d265adaa1" } ,{ "testCaseDescription": "javascript-template-string-delete-replacement-test", @@ -184,8 +179,7 @@ ] } }, - "summary": "Deleted the '`multi line`' template string", - "tag": "JSONSummary" + "summary": "Deleted the '`multi line`' template string" }, { "span": { @@ -200,8 +194,7 @@ ] } }, - "summary": "Deleted the '`one line`' template string", - "tag": "JSONSummary" + "summary": "Deleted the '`one line`' template string" }, { "span": { @@ -216,8 +209,7 @@ ] } }, - "summary": "Added the '`multi line`' template string", - "tag": "JSONSummary" + "summary": "Added the '`multi line`' template string" } ] }, @@ -226,9 +218,9 @@ "filePaths": [ "template-string.js" ], - "sha1": "90298bc75cf5d9c6227abf73fad97faae4e47c59", + "sha1": "7b2f1a9735c2c7e49481be1f7ca76a4d265adaa1", "gitDir": "test/corpus/repos/javascript", - "sha2": "8769cac2a58027e4e04e72860fa8d37db5752dac" + "sha2": "897d45ce3ce2e3abebd4f6c51f50ed8f3677b3bd" } ,{ "testCaseDescription": "javascript-template-string-delete-test", @@ -248,8 +240,7 @@ ] } }, - "summary": "Deleted the '`one line`' template string", - "tag": "JSONSummary" + "summary": "Deleted the '`one line`' template string" } ] }, @@ -258,9 +249,9 @@ "filePaths": [ "template-string.js" ], - "sha1": "8769cac2a58027e4e04e72860fa8d37db5752dac", + "sha1": "897d45ce3ce2e3abebd4f6c51f50ed8f3677b3bd", "gitDir": "test/corpus/repos/javascript", - "sha2": "7e0fb2d00a7df954f0b8f7c8ec3f5473fa04df97" + "sha2": "6fb06ea1442e30240106f1f36d59bd06ab2edb1f" } ,{ "testCaseDescription": "javascript-template-string-delete-rest-test", @@ -280,8 +271,7 @@ ] } }, - "summary": "Deleted the '`multi line`' template string", - "tag": "JSONSummary" + "summary": "Deleted the '`multi line`' template string" } ] }, @@ -290,7 +280,7 @@ "filePaths": [ "template-string.js" ], - "sha1": "7e0fb2d00a7df954f0b8f7c8ec3f5473fa04df97", + "sha1": "6fb06ea1442e30240106f1f36d59bd06ab2edb1f", "gitDir": "test/corpus/repos/javascript", - "sha2": "85d810a0c973ca0394d96cd18baacac324ce884f" + "sha2": "8df53a54c07fb78bfcd4ee6537e27adcb642531f" }] diff --git a/test/corpus/diff-summaries/javascript/ternary.json b/test/corpus/diff-summaries/javascript/ternary.json index 754e9e8cb..e613139d9 100644 --- a/test/corpus/diff-summaries/javascript/ternary.json +++ b/test/corpus/diff-summaries/javascript/ternary.json @@ -16,8 +16,7 @@ ] } }, - "summary": "Added the 'condition' ternary expression", - "tag": "JSONSummary" + "summary": "Added the 'condition' ternary expression" } ] }, @@ -26,9 +25,9 @@ "filePaths": [ "ternary.js" ], - "sha1": "35ef6a37614f71575ccfb227aa8e9984c3b6d87c", + "sha1": "b5446feffd11ca904e2726a11bbc705545843599", "gitDir": "test/corpus/repos/javascript", - "sha2": "0f779997d2c8ddaf9eb3c0c24d0ecd4416e5b353" + "sha2": "4fbda1abcb8e30b6210e9bca5816014b7eff3407" } ,{ "testCaseDescription": "javascript-ternary-replacement-insert-test", @@ -48,8 +47,7 @@ ] } }, - "summary": "Added the 'x.y' assignment", - "tag": "JSONSummary" + "summary": "Added the 'x.y' assignment" }, { "span": { @@ -64,8 +62,7 @@ ] } }, - "summary": "Added the 'condition' ternary expression", - "tag": "JSONSummary" + "summary": "Added the 'condition' ternary expression" } ] }, @@ -74,9 +71,9 @@ "filePaths": [ "ternary.js" ], - "sha1": "0f779997d2c8ddaf9eb3c0c24d0ecd4416e5b353", + "sha1": "4fbda1abcb8e30b6210e9bca5816014b7eff3407", "gitDir": "test/corpus/repos/javascript", - "sha2": "f3a901fb98a9e4443742c1502d154227c1e29be5" + "sha2": "5a36618a7c9b673f065008726471679618abb60a" } ,{ "testCaseDescription": "javascript-ternary-delete-insert-test", @@ -96,8 +93,7 @@ ] } }, - "summary": "Added the 'condition' ternary expression", - "tag": "JSONSummary" + "summary": "Added the 'condition' ternary expression" }, { "span": { @@ -112,8 +108,7 @@ ] } }, - "summary": "Deleted the 'x.y' assignment", - "tag": "JSONSummary" + "summary": "Deleted the 'x.y' assignment" } ] }, @@ -122,9 +117,9 @@ "filePaths": [ "ternary.js" ], - "sha1": "f3a901fb98a9e4443742c1502d154227c1e29be5", + "sha1": "5a36618a7c9b673f065008726471679618abb60a", "gitDir": "test/corpus/repos/javascript", - "sha2": "5f6d7b254553b22a73010e4d353197a09b929238" + "sha2": "7ac6d0565373cc2cf7e3aa3bdf51754c636b678d" } ,{ "testCaseDescription": "javascript-ternary-replacement-test", @@ -144,8 +139,7 @@ ] } }, - "summary": "Added the 'x.y' assignment", - "tag": "JSONSummary" + "summary": "Added the 'x.y' assignment" }, { "span": { @@ -160,8 +154,7 @@ ] } }, - "summary": "Deleted the 'condition' ternary expression", - "tag": "JSONSummary" + "summary": "Deleted the 'condition' ternary expression" } ] }, @@ -170,9 +163,9 @@ "filePaths": [ "ternary.js" ], - "sha1": "5f6d7b254553b22a73010e4d353197a09b929238", + "sha1": "7ac6d0565373cc2cf7e3aa3bdf51754c636b678d", "gitDir": "test/corpus/repos/javascript", - "sha2": "ad6319a0f7acc94d32e996cae0981e1e40bcf7d1" + "sha2": "90230dd8f3982615b5a2f7d9c96f7ebe6ef91a5a" } ,{ "testCaseDescription": "javascript-ternary-delete-replacement-test", @@ -192,8 +185,7 @@ ] } }, - "summary": "Deleted the 'x.y' assignment", - "tag": "JSONSummary" + "summary": "Deleted the 'x.y' assignment" }, { "span": { @@ -208,8 +200,7 @@ ] } }, - "summary": "Deleted the 'condition' ternary expression", - "tag": "JSONSummary" + "summary": "Deleted the 'condition' ternary expression" }, { "span": { @@ -224,8 +215,7 @@ ] } }, - "summary": "Added the 'x.y' assignment", - "tag": "JSONSummary" + "summary": "Added the 'x.y' assignment" } ] }, @@ -234,9 +224,9 @@ "filePaths": [ "ternary.js" ], - "sha1": "ad6319a0f7acc94d32e996cae0981e1e40bcf7d1", + "sha1": "90230dd8f3982615b5a2f7d9c96f7ebe6ef91a5a", "gitDir": "test/corpus/repos/javascript", - "sha2": "ee87ff1df9fe1e63ee1afcda1d4922dc732036c3" + "sha2": "7a926ee6d785e921b0253f556626ab7b2faa0d27" } ,{ "testCaseDescription": "javascript-ternary-delete-test", @@ -256,8 +246,7 @@ ] } }, - "summary": "Deleted the 'condition' ternary expression", - "tag": "JSONSummary" + "summary": "Deleted the 'condition' ternary expression" } ] }, @@ -266,9 +255,9 @@ "filePaths": [ "ternary.js" ], - "sha1": "ee87ff1df9fe1e63ee1afcda1d4922dc732036c3", + "sha1": "7a926ee6d785e921b0253f556626ab7b2faa0d27", "gitDir": "test/corpus/repos/javascript", - "sha2": "d38b443c92e9a74d094943d3ee1893f57a075a30" + "sha2": "88c0457d70f6e468e3c6fc7ba3982a31c57d80dc" } ,{ "testCaseDescription": "javascript-ternary-delete-rest-test", @@ -288,8 +277,7 @@ ] } }, - "summary": "Deleted the 'x.y' assignment", - "tag": "JSONSummary" + "summary": "Deleted the 'x.y' assignment" } ] }, @@ -298,7 +286,7 @@ "filePaths": [ "ternary.js" ], - "sha1": "d38b443c92e9a74d094943d3ee1893f57a075a30", + "sha1": "88c0457d70f6e468e3c6fc7ba3982a31c57d80dc", "gitDir": "test/corpus/repos/javascript", - "sha2": "d66448c6fbbdc40a36b1c5f8b505ba85856567c5" + "sha2": "9fd6bf4586ccb3910de1ff443d7928bce68977cb" }] diff --git a/test/corpus/diff-summaries/javascript/this-expression.json b/test/corpus/diff-summaries/javascript/this-expression.json index 68b6fe959..ec2a91ba3 100644 --- a/test/corpus/diff-summaries/javascript/this-expression.json +++ b/test/corpus/diff-summaries/javascript/this-expression.json @@ -16,8 +16,7 @@ ] } }, - "summary": "Added the 'this' identifier", - "tag": "JSONSummary" + "summary": "Added the 'this' identifier" } ] }, @@ -26,9 +25,9 @@ "filePaths": [ "this-expression.js" ], - "sha1": "7b97e72d7c0e6b3898be9d1deb06da6b7ea09764", + "sha1": "6a44e531842b97c2a60eb0fb38c57fe35035cf16", "gitDir": "test/corpus/repos/javascript", - "sha2": "a2a8fb25467bf9403e4de37a8f434852ed8f848b" + "sha2": "915f0a11edc274872a8147949183e8b07c9fad4b" } ,{ "testCaseDescription": "javascript-this-expression-replacement-insert-test", @@ -48,8 +47,7 @@ ] } }, - "summary": "Added the 'this' return statement", - "tag": "JSONSummary" + "summary": "Added the 'this' return statement" }, { "span": { @@ -64,8 +62,7 @@ ] } }, - "summary": "Added the 'this' identifier", - "tag": "JSONSummary" + "summary": "Added the 'this' identifier" } ] }, @@ -74,9 +71,9 @@ "filePaths": [ "this-expression.js" ], - "sha1": "a2a8fb25467bf9403e4de37a8f434852ed8f848b", + "sha1": "915f0a11edc274872a8147949183e8b07c9fad4b", "gitDir": "test/corpus/repos/javascript", - "sha2": "6625c63c5f06e702ef97f2fdc3a25ff525e70e4f" + "sha2": "adb919fd11be97d945483b00e4d2f37856e483b6" } ,{ "testCaseDescription": "javascript-this-expression-delete-insert-test", @@ -96,8 +93,7 @@ ] } }, - "summary": "Added the 'this' identifier", - "tag": "JSONSummary" + "summary": "Added the 'this' identifier" }, { "span": { @@ -112,8 +108,7 @@ ] } }, - "summary": "Deleted the 'this' return statement", - "tag": "JSONSummary" + "summary": "Deleted the 'this' return statement" } ] }, @@ -122,9 +117,9 @@ "filePaths": [ "this-expression.js" ], - "sha1": "6625c63c5f06e702ef97f2fdc3a25ff525e70e4f", + "sha1": "adb919fd11be97d945483b00e4d2f37856e483b6", "gitDir": "test/corpus/repos/javascript", - "sha2": "ffbed3418a24653fbd26b4cd35deb23988f30198" + "sha2": "877ee8b57e204cd9e3569f3adaad096ec8a970dd" } ,{ "testCaseDescription": "javascript-this-expression-replacement-test", @@ -144,8 +139,7 @@ ] } }, - "summary": "Added the 'this' return statement", - "tag": "JSONSummary" + "summary": "Added the 'this' return statement" }, { "span": { @@ -160,8 +154,7 @@ ] } }, - "summary": "Deleted the 'this' identifier", - "tag": "JSONSummary" + "summary": "Deleted the 'this' identifier" } ] }, @@ -170,9 +163,9 @@ "filePaths": [ "this-expression.js" ], - "sha1": "ffbed3418a24653fbd26b4cd35deb23988f30198", + "sha1": "877ee8b57e204cd9e3569f3adaad096ec8a970dd", "gitDir": "test/corpus/repos/javascript", - "sha2": "7db7900eb04a66af0196e73999687ba83b168947" + "sha2": "2a193071c5327473bc0e781d94e32a64495884eb" } ,{ "testCaseDescription": "javascript-this-expression-delete-replacement-test", @@ -192,8 +185,7 @@ ] } }, - "summary": "Deleted the 'this' return statement", - "tag": "JSONSummary" + "summary": "Deleted the 'this' return statement" }, { "span": { @@ -208,8 +200,7 @@ ] } }, - "summary": "Deleted the 'this' identifier", - "tag": "JSONSummary" + "summary": "Deleted the 'this' identifier" }, { "span": { @@ -224,8 +215,7 @@ ] } }, - "summary": "Added the 'this' return statement", - "tag": "JSONSummary" + "summary": "Added the 'this' return statement" } ] }, @@ -234,9 +224,9 @@ "filePaths": [ "this-expression.js" ], - "sha1": "7db7900eb04a66af0196e73999687ba83b168947", + "sha1": "2a193071c5327473bc0e781d94e32a64495884eb", "gitDir": "test/corpus/repos/javascript", - "sha2": "220159fc73518eb2ba3c195c9d230c523137fb9d" + "sha2": "916921ca606d1206fa980e030ed31cd87966e946" } ,{ "testCaseDescription": "javascript-this-expression-delete-test", @@ -256,8 +246,7 @@ ] } }, - "summary": "Deleted the 'this' identifier", - "tag": "JSONSummary" + "summary": "Deleted the 'this' identifier" } ] }, @@ -266,9 +255,9 @@ "filePaths": [ "this-expression.js" ], - "sha1": "220159fc73518eb2ba3c195c9d230c523137fb9d", + "sha1": "916921ca606d1206fa980e030ed31cd87966e946", "gitDir": "test/corpus/repos/javascript", - "sha2": "3594ddd1cbf054031d468b2ce85d2c617ac5bd51" + "sha2": "ccf1e1fa57208cdefeb650390c4153ba13d60b23" } ,{ "testCaseDescription": "javascript-this-expression-delete-rest-test", @@ -288,8 +277,7 @@ ] } }, - "summary": "Deleted the 'this' return statement", - "tag": "JSONSummary" + "summary": "Deleted the 'this' return statement" } ] }, @@ -298,7 +286,7 @@ "filePaths": [ "this-expression.js" ], - "sha1": "3594ddd1cbf054031d468b2ce85d2c617ac5bd51", + "sha1": "ccf1e1fa57208cdefeb650390c4153ba13d60b23", "gitDir": "test/corpus/repos/javascript", - "sha2": "72aab09a49d2096eccd1ff0f785ef1b2d9283961" + "sha2": "027732543c3974844a2f660a3ee74c0837a5b055" }] diff --git a/test/corpus/diff-summaries/javascript/throw-statement.json b/test/corpus/diff-summaries/javascript/throw-statement.json index aee57f66a..4f3c6e7e5 100644 --- a/test/corpus/diff-summaries/javascript/throw-statement.json +++ b/test/corpus/diff-summaries/javascript/throw-statement.json @@ -16,8 +16,7 @@ ] } }, - "summary": "Added the 'new Error(\"uh oh\")' throw statement", - "tag": "JSONSummary" + "summary": "Added the 'new Error(\"uh oh\")' throw statement" } ] }, @@ -26,9 +25,9 @@ "filePaths": [ "throw-statement.js" ], - "sha1": "4703a7002d32db2234780ed17ed8bf95a45569ca", + "sha1": "04ac626daa098bf596f572115ce36f8cf31b84df", "gitDir": "test/corpus/repos/javascript", - "sha2": "2518b94568794c2a248421a57291d345fc132b7f" + "sha2": "6504a2a9d3f565d5812bbd79e02f53609761fe92" } ,{ "testCaseDescription": "javascript-throw-statement-replacement-insert-test", @@ -48,8 +47,7 @@ ] } }, - "summary": "Added the 'new Error(\"oooooops\")' throw statement", - "tag": "JSONSummary" + "summary": "Added the 'new Error(\"oooooops\")' throw statement" }, { "span": { @@ -64,8 +62,7 @@ ] } }, - "summary": "Added the 'new Error(\"uh oh\")' throw statement", - "tag": "JSONSummary" + "summary": "Added the 'new Error(\"uh oh\")' throw statement" } ] }, @@ -74,9 +71,9 @@ "filePaths": [ "throw-statement.js" ], - "sha1": "2518b94568794c2a248421a57291d345fc132b7f", + "sha1": "6504a2a9d3f565d5812bbd79e02f53609761fe92", "gitDir": "test/corpus/repos/javascript", - "sha2": "18284196ba4ca0689123160a21accbfc055487bb" + "sha2": "5ea11da0cbfa31b113fe4c0c26a1949a6a2d12bd" } ,{ "testCaseDescription": "javascript-throw-statement-delete-insert-test", @@ -108,8 +105,7 @@ } ] }, - "summary": "Replaced the \"oooooops\" string with the \"uh oh\" string in the Error(\"uh oh\") function call", - "tag": "JSONSummary" + "summary": "Replaced the \"oooooops\" string with the \"uh oh\" string in the Error(\"uh oh\") function call" } ] }, @@ -118,9 +114,9 @@ "filePaths": [ "throw-statement.js" ], - "sha1": "18284196ba4ca0689123160a21accbfc055487bb", + "sha1": "5ea11da0cbfa31b113fe4c0c26a1949a6a2d12bd", "gitDir": "test/corpus/repos/javascript", - "sha2": "1de92de9bdc5fa85de0e9b5b5dc5c23590ac2566" + "sha2": "47633d9af7926f59a4a8555688683cc43c055266" } ,{ "testCaseDescription": "javascript-throw-statement-replacement-test", @@ -152,8 +148,7 @@ } ] }, - "summary": "Replaced the \"uh oh\" string with the \"oooooops\" string in the Error(\"oooooops\") function call", - "tag": "JSONSummary" + "summary": "Replaced the \"uh oh\" string with the \"oooooops\" string in the Error(\"oooooops\") function call" } ] }, @@ -162,9 +157,9 @@ "filePaths": [ "throw-statement.js" ], - "sha1": "1de92de9bdc5fa85de0e9b5b5dc5c23590ac2566", + "sha1": "47633d9af7926f59a4a8555688683cc43c055266", "gitDir": "test/corpus/repos/javascript", - "sha2": "d48e3de54842bdfb75cd8abeb4cebdcd43b877a4" + "sha2": "4e39f432c9e0d8a9f126b91f7ea54d21822c7c04" } ,{ "testCaseDescription": "javascript-throw-statement-delete-replacement-test", @@ -184,8 +179,7 @@ ] } }, - "summary": "Deleted the 'new Error(\"oooooops\")' throw statement", - "tag": "JSONSummary" + "summary": "Deleted the 'new Error(\"oooooops\")' throw statement" }, { "span": { @@ -200,8 +194,7 @@ ] } }, - "summary": "Deleted the 'new Error(\"uh oh\")' throw statement", - "tag": "JSONSummary" + "summary": "Deleted the 'new Error(\"uh oh\")' throw statement" }, { "span": { @@ -216,8 +209,7 @@ ] } }, - "summary": "Added the 'new Error(\"oooooops\")' throw statement", - "tag": "JSONSummary" + "summary": "Added the 'new Error(\"oooooops\")' throw statement" } ] }, @@ -226,9 +218,9 @@ "filePaths": [ "throw-statement.js" ], - "sha1": "d48e3de54842bdfb75cd8abeb4cebdcd43b877a4", + "sha1": "4e39f432c9e0d8a9f126b91f7ea54d21822c7c04", "gitDir": "test/corpus/repos/javascript", - "sha2": "7968d5456d2cae631c2ad1a3541972e8b3fbec42" + "sha2": "09ebd0d64a6252d651e35cf07c181750d7b1da40" } ,{ "testCaseDescription": "javascript-throw-statement-delete-test", @@ -248,8 +240,7 @@ ] } }, - "summary": "Deleted the 'new Error(\"uh oh\")' throw statement", - "tag": "JSONSummary" + "summary": "Deleted the 'new Error(\"uh oh\")' throw statement" } ] }, @@ -258,9 +249,9 @@ "filePaths": [ "throw-statement.js" ], - "sha1": "7968d5456d2cae631c2ad1a3541972e8b3fbec42", + "sha1": "09ebd0d64a6252d651e35cf07c181750d7b1da40", "gitDir": "test/corpus/repos/javascript", - "sha2": "b2a674bd06b1fd6701d58556d05daf118bd513fc" + "sha2": "4da8a2dd13d1b62a139f102cf2d13ce0cf6f3bb7" } ,{ "testCaseDescription": "javascript-throw-statement-delete-rest-test", @@ -280,8 +271,7 @@ ] } }, - "summary": "Deleted the 'new Error(\"oooooops\")' throw statement", - "tag": "JSONSummary" + "summary": "Deleted the 'new Error(\"oooooops\")' throw statement" } ] }, @@ -290,7 +280,7 @@ "filePaths": [ "throw-statement.js" ], - "sha1": "b2a674bd06b1fd6701d58556d05daf118bd513fc", + "sha1": "4da8a2dd13d1b62a139f102cf2d13ce0cf6f3bb7", "gitDir": "test/corpus/repos/javascript", - "sha2": "a11797b72e3d4338dc9efc6183177921bc93609e" + "sha2": "5c30863954c846e6487626965891f282d42e6b84" }] diff --git a/test/corpus/diff-summaries/javascript/true.json b/test/corpus/diff-summaries/javascript/true.json index c00dba9ae..16f71d4a7 100644 --- a/test/corpus/diff-summaries/javascript/true.json +++ b/test/corpus/diff-summaries/javascript/true.json @@ -16,8 +16,7 @@ ] } }, - "summary": "Added 'true'", - "tag": "JSONSummary" + "summary": "Added 'true'" } ] }, @@ -26,9 +25,9 @@ "filePaths": [ "true.js" ], - "sha1": "e8bb54ef7035c6f0ab215c7f0af3134871bd2d37", + "sha1": "f6baf27a65896e7e502d6ec646cb3cbbd7e206f6", "gitDir": "test/corpus/repos/javascript", - "sha2": "95ae5cef054c9d3c1a77535d0fd7b9261b13aeb9" + "sha2": "5091492afacae27e07b10a11965b4b5338f092c8" } ,{ "testCaseDescription": "javascript-true-replacement-insert-test", @@ -48,8 +47,7 @@ ] } }, - "summary": "Added the 'true' return statement", - "tag": "JSONSummary" + "summary": "Added the 'true' return statement" }, { "span": { @@ -64,8 +62,7 @@ ] } }, - "summary": "Added 'true'", - "tag": "JSONSummary" + "summary": "Added 'true'" } ] }, @@ -74,9 +71,9 @@ "filePaths": [ "true.js" ], - "sha1": "95ae5cef054c9d3c1a77535d0fd7b9261b13aeb9", + "sha1": "5091492afacae27e07b10a11965b4b5338f092c8", "gitDir": "test/corpus/repos/javascript", - "sha2": "81f477d087ea9dc02376766508a16e7f01c4bcc3" + "sha2": "3bbd68f2e51402ce75780e5af72c03512991d95b" } ,{ "testCaseDescription": "javascript-true-delete-insert-test", @@ -96,8 +93,7 @@ ] } }, - "summary": "Added 'true'", - "tag": "JSONSummary" + "summary": "Added 'true'" }, { "span": { @@ -112,8 +108,7 @@ ] } }, - "summary": "Deleted the 'true' return statement", - "tag": "JSONSummary" + "summary": "Deleted the 'true' return statement" } ] }, @@ -122,9 +117,9 @@ "filePaths": [ "true.js" ], - "sha1": "81f477d087ea9dc02376766508a16e7f01c4bcc3", + "sha1": "3bbd68f2e51402ce75780e5af72c03512991d95b", "gitDir": "test/corpus/repos/javascript", - "sha2": "75e755b738850d3338c31320413ad8696884fe31" + "sha2": "12760109620d0e2aebc964bf10793a9018a7a993" } ,{ "testCaseDescription": "javascript-true-replacement-test", @@ -144,8 +139,7 @@ ] } }, - "summary": "Added the 'true' return statement", - "tag": "JSONSummary" + "summary": "Added the 'true' return statement" }, { "span": { @@ -160,8 +154,7 @@ ] } }, - "summary": "Deleted 'true'", - "tag": "JSONSummary" + "summary": "Deleted 'true'" } ] }, @@ -170,9 +163,9 @@ "filePaths": [ "true.js" ], - "sha1": "75e755b738850d3338c31320413ad8696884fe31", + "sha1": "12760109620d0e2aebc964bf10793a9018a7a993", "gitDir": "test/corpus/repos/javascript", - "sha2": "6d14f16bb963f4554bd80dc780330ffc3dc66ac0" + "sha2": "6b269c9b079a987453884c3d4f894bfb4e76be70" } ,{ "testCaseDescription": "javascript-true-delete-replacement-test", @@ -192,8 +185,7 @@ ] } }, - "summary": "Deleted the 'true' return statement", - "tag": "JSONSummary" + "summary": "Deleted the 'true' return statement" }, { "span": { @@ -208,8 +200,7 @@ ] } }, - "summary": "Deleted 'true'", - "tag": "JSONSummary" + "summary": "Deleted 'true'" }, { "span": { @@ -224,8 +215,7 @@ ] } }, - "summary": "Added the 'true' return statement", - "tag": "JSONSummary" + "summary": "Added the 'true' return statement" } ] }, @@ -234,9 +224,9 @@ "filePaths": [ "true.js" ], - "sha1": "6d14f16bb963f4554bd80dc780330ffc3dc66ac0", + "sha1": "6b269c9b079a987453884c3d4f894bfb4e76be70", "gitDir": "test/corpus/repos/javascript", - "sha2": "5ed630e1aab4b6b806751b920fc74d9d05081fb2" + "sha2": "0fe461d1797041345efd7168414a5d143c47a0b8" } ,{ "testCaseDescription": "javascript-true-delete-test", @@ -256,8 +246,7 @@ ] } }, - "summary": "Deleted 'true'", - "tag": "JSONSummary" + "summary": "Deleted 'true'" } ] }, @@ -266,9 +255,9 @@ "filePaths": [ "true.js" ], - "sha1": "5ed630e1aab4b6b806751b920fc74d9d05081fb2", + "sha1": "0fe461d1797041345efd7168414a5d143c47a0b8", "gitDir": "test/corpus/repos/javascript", - "sha2": "aced0cd3388a00dec08265c65fabcbdc18195d78" + "sha2": "f6239893bd02de6e0a7e7f5ef678ad2421d0719e" } ,{ "testCaseDescription": "javascript-true-delete-rest-test", @@ -288,8 +277,7 @@ ] } }, - "summary": "Deleted the 'true' return statement", - "tag": "JSONSummary" + "summary": "Deleted the 'true' return statement" } ] }, @@ -298,7 +286,7 @@ "filePaths": [ "true.js" ], - "sha1": "aced0cd3388a00dec08265c65fabcbdc18195d78", + "sha1": "f6239893bd02de6e0a7e7f5ef678ad2421d0719e", "gitDir": "test/corpus/repos/javascript", - "sha2": "ec94fd01e01d796cac3744f43515ffaad64f1fbf" + "sha2": "b5f63d0fc82f7a027e684d209d08915d0b2bf95c" }] diff --git a/test/corpus/diff-summaries/javascript/try-statement.json b/test/corpus/diff-summaries/javascript/try-statement.json index fe8c431e2..0e883c3d6 100644 --- a/test/corpus/diff-summaries/javascript/try-statement.json +++ b/test/corpus/diff-summaries/javascript/try-statement.json @@ -16,8 +16,7 @@ ] } }, - "summary": "Added the '{ f; }' try statement", - "tag": "JSONSummary" + "summary": "Added the '{ f; }' try statement" } ] }, @@ -26,9 +25,9 @@ "filePaths": [ "try-statement.js" ], - "sha1": "edf461750d55ec70810d768af2bc471f00736c6f", + "sha1": "b908a6724f0ad01f8801ea57866f313307e6b319", "gitDir": "test/corpus/repos/javascript", - "sha2": "dd72da3c12c1af00ba82506f288d1e07e0329005" + "sha2": "d3adba31d9e7e79d07e703ad2a6967562b220f6b" } ,{ "testCaseDescription": "javascript-try-statement-replacement-insert-test", @@ -48,8 +47,7 @@ ] } }, - "summary": "Added the '{ f; }' try statement", - "tag": "JSONSummary" + "summary": "Added the '{ f; }' try statement" }, { "span": { @@ -64,8 +62,7 @@ ] } }, - "summary": "Added the '{ f; }' try statement", - "tag": "JSONSummary" + "summary": "Added the '{ f; }' try statement" } ] }, @@ -74,9 +71,9 @@ "filePaths": [ "try-statement.js" ], - "sha1": "dd72da3c12c1af00ba82506f288d1e07e0329005", + "sha1": "d3adba31d9e7e79d07e703ad2a6967562b220f6b", "gitDir": "test/corpus/repos/javascript", - "sha2": "aef5631ddb1eadeea819782d6cad5ebaa3267263" + "sha2": "c1fc74cb0f5db63aee48f72adcd8abccccbc931c" } ,{ "testCaseDescription": "javascript-try-statement-delete-insert-test", @@ -108,8 +105,7 @@ } ] }, - "summary": "Replaced the 'h' identifier with the 'g' identifier", - "tag": "JSONSummary" + "summary": "Replaced the 'h' identifier with the 'g' identifier" }, { "span": { @@ -136,8 +132,7 @@ } ] }, - "summary": "Replaced the 'g' identifier with the 'h' identifier", - "tag": "JSONSummary" + "summary": "Replaced the 'g' identifier with the 'h' identifier" } ] }, @@ -146,9 +141,9 @@ "filePaths": [ "try-statement.js" ], - "sha1": "aef5631ddb1eadeea819782d6cad5ebaa3267263", + "sha1": "c1fc74cb0f5db63aee48f72adcd8abccccbc931c", "gitDir": "test/corpus/repos/javascript", - "sha2": "ed026d2a79ed7e2935aa2c6654802265cfd1e277" + "sha2": "18a5e0f40787e268714e8c7bd3e1641d76d78319" } ,{ "testCaseDescription": "javascript-try-statement-replacement-test", @@ -180,8 +175,7 @@ } ] }, - "summary": "Replaced the 'g' identifier with the 'h' identifier", - "tag": "JSONSummary" + "summary": "Replaced the 'g' identifier with the 'h' identifier" }, { "span": { @@ -208,8 +202,7 @@ } ] }, - "summary": "Replaced the 'h' identifier with the 'g' identifier", - "tag": "JSONSummary" + "summary": "Replaced the 'h' identifier with the 'g' identifier" } ] }, @@ -218,9 +211,9 @@ "filePaths": [ "try-statement.js" ], - "sha1": "ed026d2a79ed7e2935aa2c6654802265cfd1e277", + "sha1": "18a5e0f40787e268714e8c7bd3e1641d76d78319", "gitDir": "test/corpus/repos/javascript", - "sha2": "7e2d4a57ded708e456a65e74de6aa306f109e7f1" + "sha2": "f836874a0d43f61e721d253cf3f97fd0a83cb6e7" } ,{ "testCaseDescription": "javascript-try-statement-delete-replacement-test", @@ -240,8 +233,7 @@ ] } }, - "summary": "Deleted the '{ f; }' try statement", - "tag": "JSONSummary" + "summary": "Deleted the '{ f; }' try statement" }, { "span": { @@ -256,8 +248,7 @@ ] } }, - "summary": "Deleted the '{ f; }' try statement", - "tag": "JSONSummary" + "summary": "Deleted the '{ f; }' try statement" }, { "span": { @@ -272,8 +263,7 @@ ] } }, - "summary": "Added the '{ f; }' try statement", - "tag": "JSONSummary" + "summary": "Added the '{ f; }' try statement" } ] }, @@ -282,9 +272,9 @@ "filePaths": [ "try-statement.js" ], - "sha1": "7e2d4a57ded708e456a65e74de6aa306f109e7f1", + "sha1": "f836874a0d43f61e721d253cf3f97fd0a83cb6e7", "gitDir": "test/corpus/repos/javascript", - "sha2": "a08334179979e507269d2d4d225b43fabdf08231" + "sha2": "8776c024182abad3bb3f5f68e999e1172fd0bce0" } ,{ "testCaseDescription": "javascript-try-statement-delete-test", @@ -304,8 +294,7 @@ ] } }, - "summary": "Deleted the '{ f; }' try statement", - "tag": "JSONSummary" + "summary": "Deleted the '{ f; }' try statement" } ] }, @@ -314,9 +303,9 @@ "filePaths": [ "try-statement.js" ], - "sha1": "a08334179979e507269d2d4d225b43fabdf08231", + "sha1": "8776c024182abad3bb3f5f68e999e1172fd0bce0", "gitDir": "test/corpus/repos/javascript", - "sha2": "6375ef5c9ef95bc52a4f4d0b27b25a45ee6d4ad0" + "sha2": "fb43fddce814a12e5f3a96d13a6a533ea965218c" } ,{ "testCaseDescription": "javascript-try-statement-delete-rest-test", @@ -336,8 +325,7 @@ ] } }, - "summary": "Deleted the '{ f; }' try statement", - "tag": "JSONSummary" + "summary": "Deleted the '{ f; }' try statement" } ] }, @@ -346,7 +334,7 @@ "filePaths": [ "try-statement.js" ], - "sha1": "6375ef5c9ef95bc52a4f4d0b27b25a45ee6d4ad0", + "sha1": "fb43fddce814a12e5f3a96d13a6a533ea965218c", "gitDir": "test/corpus/repos/javascript", - "sha2": "d1920048204583b13ae78843de8cb2aceb164574" + "sha2": "f03ea63f2c081eb44cc3094034c2320fa50f8520" }] diff --git a/test/corpus/diff-summaries/javascript/type-operator.json b/test/corpus/diff-summaries/javascript/type-operator.json index 8b07b8e39..393dfdf21 100644 --- a/test/corpus/diff-summaries/javascript/type-operator.json +++ b/test/corpus/diff-summaries/javascript/type-operator.json @@ -16,8 +16,7 @@ ] } }, - "summary": "Added the 'typeof x' operator", - "tag": "JSONSummary" + "summary": "Added the 'typeof x' operator" } ] }, @@ -26,9 +25,9 @@ "filePaths": [ "type-operator.js" ], - "sha1": "184d21574db41e0343ee9e0ebe166495b6205fff", + "sha1": "6eeb048dd356c28a76842bafe0ff471aca4fc709", "gitDir": "test/corpus/repos/javascript", - "sha2": "720e0e4fb3fd308a3a024852f65dccb5a3159645" + "sha2": "ae302058d381bfe2242f8af75707d16d9bc5f9c6" } ,{ "testCaseDescription": "javascript-type-operator-replacement-insert-test", @@ -48,8 +47,7 @@ ] } }, - "summary": "Added the 'x instanceof String' operator", - "tag": "JSONSummary" + "summary": "Added the 'x instanceof String' operator" }, { "span": { @@ -64,8 +62,7 @@ ] } }, - "summary": "Added the 'typeof x' operator", - "tag": "JSONSummary" + "summary": "Added the 'typeof x' operator" } ] }, @@ -74,9 +71,9 @@ "filePaths": [ "type-operator.js" ], - "sha1": "720e0e4fb3fd308a3a024852f65dccb5a3159645", + "sha1": "ae302058d381bfe2242f8af75707d16d9bc5f9c6", "gitDir": "test/corpus/repos/javascript", - "sha2": "ba9af83b00f98272bde1cab0c624397e934650c0" + "sha2": "70ff969d615bb1e12f9c83a34430c4eecf5e1423" } ,{ "testCaseDescription": "javascript-type-operator-delete-insert-test", @@ -96,8 +93,7 @@ ] } }, - "summary": "Deleted the 'String' identifier", - "tag": "JSONSummary" + "summary": "Deleted the 'String' identifier" } ] }, @@ -106,9 +102,9 @@ "filePaths": [ "type-operator.js" ], - "sha1": "ba9af83b00f98272bde1cab0c624397e934650c0", + "sha1": "70ff969d615bb1e12f9c83a34430c4eecf5e1423", "gitDir": "test/corpus/repos/javascript", - "sha2": "71d60e89b4137fd4a2e0cc552789f9cfc04264c3" + "sha2": "4e7d94a429cfea4cfb43bee17420bdf2cf31857e" } ,{ "testCaseDescription": "javascript-type-operator-replacement-test", @@ -128,8 +124,7 @@ ] } }, - "summary": "Added the 'String' identifier", - "tag": "JSONSummary" + "summary": "Added the 'String' identifier" } ] }, @@ -138,9 +133,9 @@ "filePaths": [ "type-operator.js" ], - "sha1": "71d60e89b4137fd4a2e0cc552789f9cfc04264c3", + "sha1": "4e7d94a429cfea4cfb43bee17420bdf2cf31857e", "gitDir": "test/corpus/repos/javascript", - "sha2": "1c735c0485ca5c653addd5814e52595ac5787cdb" + "sha2": "5f0e7b153777bb043786fa66aee9e38978d66762" } ,{ "testCaseDescription": "javascript-type-operator-delete-replacement-test", @@ -160,8 +155,7 @@ ] } }, - "summary": "Deleted the 'x instanceof String' operator", - "tag": "JSONSummary" + "summary": "Deleted the 'x instanceof String' operator" }, { "span": { @@ -176,8 +170,7 @@ ] } }, - "summary": "Deleted the 'typeof x' operator", - "tag": "JSONSummary" + "summary": "Deleted the 'typeof x' operator" }, { "span": { @@ -192,8 +185,7 @@ ] } }, - "summary": "Added the 'x instanceof String' operator", - "tag": "JSONSummary" + "summary": "Added the 'x instanceof String' operator" } ] }, @@ -202,9 +194,9 @@ "filePaths": [ "type-operator.js" ], - "sha1": "1c735c0485ca5c653addd5814e52595ac5787cdb", + "sha1": "5f0e7b153777bb043786fa66aee9e38978d66762", "gitDir": "test/corpus/repos/javascript", - "sha2": "c85218016394b93295e0cef901de2755be8e901c" + "sha2": "9aaacd568854471edc874364923b43b5a65f6caf" } ,{ "testCaseDescription": "javascript-type-operator-delete-test", @@ -224,8 +216,7 @@ ] } }, - "summary": "Deleted the 'typeof x' operator", - "tag": "JSONSummary" + "summary": "Deleted the 'typeof x' operator" } ] }, @@ -234,9 +225,9 @@ "filePaths": [ "type-operator.js" ], - "sha1": "c85218016394b93295e0cef901de2755be8e901c", + "sha1": "9aaacd568854471edc874364923b43b5a65f6caf", "gitDir": "test/corpus/repos/javascript", - "sha2": "2928891cdd48936b69827f3ae19220bbb30d3b6e" + "sha2": "b91ec6770bb9eed6aa7f9a0b24c65d6460ba825d" } ,{ "testCaseDescription": "javascript-type-operator-delete-rest-test", @@ -256,8 +247,7 @@ ] } }, - "summary": "Deleted the 'x instanceof String' operator", - "tag": "JSONSummary" + "summary": "Deleted the 'x instanceof String' operator" } ] }, @@ -266,7 +256,7 @@ "filePaths": [ "type-operator.js" ], - "sha1": "2928891cdd48936b69827f3ae19220bbb30d3b6e", + "sha1": "b91ec6770bb9eed6aa7f9a0b24c65d6460ba825d", "gitDir": "test/corpus/repos/javascript", - "sha2": "50c9fb7f60331db7c4a5580663122bf6c875340c" + "sha2": "1d96325511c74b433e0a9c675a1e9c1a368bf222" }] diff --git a/test/corpus/diff-summaries/javascript/undefined.json b/test/corpus/diff-summaries/javascript/undefined.json index 129d33729..c9627a4d5 100644 --- a/test/corpus/diff-summaries/javascript/undefined.json +++ b/test/corpus/diff-summaries/javascript/undefined.json @@ -16,8 +16,7 @@ ] } }, - "summary": "Added the 'undefined' identifier", - "tag": "JSONSummary" + "summary": "Added the 'undefined' identifier" } ] }, @@ -26,9 +25,9 @@ "filePaths": [ "undefined.js" ], - "sha1": "3e883f3c905964aa9c04a836721989934f251368", + "sha1": "49e91b55ab4d34df9d10e18a357ecb3f9129d38b", "gitDir": "test/corpus/repos/javascript", - "sha2": "24616410c732e4ed0d2bdd366a9b7c65f1350ab9" + "sha2": "670251c94df41dfcbe8b26ad37cf7b723051a348" } ,{ "testCaseDescription": "javascript-undefined-replacement-insert-test", @@ -48,8 +47,7 @@ ] } }, - "summary": "Added the 'undefined' return statement", - "tag": "JSONSummary" + "summary": "Added the 'undefined' return statement" }, { "span": { @@ -64,8 +62,7 @@ ] } }, - "summary": "Added the 'undefined' identifier", - "tag": "JSONSummary" + "summary": "Added the 'undefined' identifier" } ] }, @@ -74,9 +71,9 @@ "filePaths": [ "undefined.js" ], - "sha1": "24616410c732e4ed0d2bdd366a9b7c65f1350ab9", + "sha1": "670251c94df41dfcbe8b26ad37cf7b723051a348", "gitDir": "test/corpus/repos/javascript", - "sha2": "65b072d0a6fc020645b06825f6575c2b445e88fe" + "sha2": "1cc3532b64f1b7f19e3676f8625a2b12cfe2630b" } ,{ "testCaseDescription": "javascript-undefined-delete-insert-test", @@ -96,8 +93,7 @@ ] } }, - "summary": "Added the 'undefined' identifier", - "tag": "JSONSummary" + "summary": "Added the 'undefined' identifier" }, { "span": { @@ -112,8 +108,7 @@ ] } }, - "summary": "Deleted the 'undefined' return statement", - "tag": "JSONSummary" + "summary": "Deleted the 'undefined' return statement" } ] }, @@ -122,9 +117,9 @@ "filePaths": [ "undefined.js" ], - "sha1": "65b072d0a6fc020645b06825f6575c2b445e88fe", + "sha1": "1cc3532b64f1b7f19e3676f8625a2b12cfe2630b", "gitDir": "test/corpus/repos/javascript", - "sha2": "844f980e3cd0425b33d6750fd10f33a7c2e52ad5" + "sha2": "db10576ffb9656dcaaba5532089eb76acf5d489f" } ,{ "testCaseDescription": "javascript-undefined-replacement-test", @@ -144,8 +139,7 @@ ] } }, - "summary": "Added the 'undefined' return statement", - "tag": "JSONSummary" + "summary": "Added the 'undefined' return statement" }, { "span": { @@ -160,8 +154,7 @@ ] } }, - "summary": "Deleted the 'undefined' identifier", - "tag": "JSONSummary" + "summary": "Deleted the 'undefined' identifier" } ] }, @@ -170,9 +163,9 @@ "filePaths": [ "undefined.js" ], - "sha1": "844f980e3cd0425b33d6750fd10f33a7c2e52ad5", + "sha1": "db10576ffb9656dcaaba5532089eb76acf5d489f", "gitDir": "test/corpus/repos/javascript", - "sha2": "0908d4dfcb1c0b86f4ca20bd055670ebbe0e9dac" + "sha2": "fd6f48b2d37f71c4e9155b4fe875371543a92961" } ,{ "testCaseDescription": "javascript-undefined-delete-replacement-test", @@ -192,8 +185,7 @@ ] } }, - "summary": "Deleted the 'undefined' return statement", - "tag": "JSONSummary" + "summary": "Deleted the 'undefined' return statement" }, { "span": { @@ -208,8 +200,7 @@ ] } }, - "summary": "Deleted the 'undefined' identifier", - "tag": "JSONSummary" + "summary": "Deleted the 'undefined' identifier" }, { "span": { @@ -224,8 +215,7 @@ ] } }, - "summary": "Added the 'undefined' return statement", - "tag": "JSONSummary" + "summary": "Added the 'undefined' return statement" } ] }, @@ -234,9 +224,9 @@ "filePaths": [ "undefined.js" ], - "sha1": "0908d4dfcb1c0b86f4ca20bd055670ebbe0e9dac", + "sha1": "fd6f48b2d37f71c4e9155b4fe875371543a92961", "gitDir": "test/corpus/repos/javascript", - "sha2": "3439b9b0f4daba5fb029403dcc7d37d7d5f147de" + "sha2": "5a182f3d30775c47d619dea99fb6912f14460f86" } ,{ "testCaseDescription": "javascript-undefined-delete-test", @@ -256,8 +246,7 @@ ] } }, - "summary": "Deleted the 'undefined' identifier", - "tag": "JSONSummary" + "summary": "Deleted the 'undefined' identifier" } ] }, @@ -266,9 +255,9 @@ "filePaths": [ "undefined.js" ], - "sha1": "3439b9b0f4daba5fb029403dcc7d37d7d5f147de", + "sha1": "5a182f3d30775c47d619dea99fb6912f14460f86", "gitDir": "test/corpus/repos/javascript", - "sha2": "fd6bea53f81c603df1baa77d61048b0c7162d3ed" + "sha2": "58439f1bf80a8b82fae2f08eb8bfc1d1a96c4a7e" } ,{ "testCaseDescription": "javascript-undefined-delete-rest-test", @@ -288,8 +277,7 @@ ] } }, - "summary": "Deleted the 'undefined' return statement", - "tag": "JSONSummary" + "summary": "Deleted the 'undefined' return statement" } ] }, @@ -298,7 +286,7 @@ "filePaths": [ "undefined.js" ], - "sha1": "fd6bea53f81c603df1baa77d61048b0c7162d3ed", + "sha1": "58439f1bf80a8b82fae2f08eb8bfc1d1a96c4a7e", "gitDir": "test/corpus/repos/javascript", - "sha2": "3e1c52cdcfb175a8271723e1584824e78861caa0" + "sha2": "a36b31965536bd78704978e111fd017722054b27" }] diff --git a/test/corpus/diff-summaries/javascript/var-declaration.json b/test/corpus/diff-summaries/javascript/var-declaration.json index 8efe6415b..29b9620b4 100644 --- a/test/corpus/diff-summaries/javascript/var-declaration.json +++ b/test/corpus/diff-summaries/javascript/var-declaration.json @@ -16,8 +16,7 @@ ] } }, - "summary": "Added the 'x' variable", - "tag": "JSONSummary" + "summary": "Added the 'x' variable" } ] }, @@ -26,9 +25,9 @@ "filePaths": [ "var-declaration.js" ], - "sha1": "9cb880c6d183e0ff29f5a379bf6bfe8a91ea75f0", + "sha1": "6f8397f676d372fb7cc681c6170eab3f00a5508b", "gitDir": "test/corpus/repos/javascript", - "sha2": "9be12afcd6174bb4ccbb9e4e203ff9c2ebd05c2f" + "sha2": "a0b5c84fbb211d943917ca1b033d0f4d69e99fab" } ,{ "testCaseDescription": "javascript-var-declaration-replacement-insert-test", @@ -48,8 +47,7 @@ ] } }, - "summary": "Added the 'x' variable", - "tag": "JSONSummary" + "summary": "Added the 'x' variable" }, { "span": { @@ -64,8 +62,7 @@ ] } }, - "summary": "Added the 'y' variable", - "tag": "JSONSummary" + "summary": "Added the 'y' variable" }, { "span": { @@ -80,8 +77,7 @@ ] } }, - "summary": "Added the 'z' variable", - "tag": "JSONSummary" + "summary": "Added the 'z' variable" }, { "span": { @@ -96,8 +92,7 @@ ] } }, - "summary": "Added the 'x' variable", - "tag": "JSONSummary" + "summary": "Added the 'x' variable" } ] }, @@ -106,9 +101,9 @@ "filePaths": [ "var-declaration.js" ], - "sha1": "9be12afcd6174bb4ccbb9e4e203ff9c2ebd05c2f", + "sha1": "a0b5c84fbb211d943917ca1b033d0f4d69e99fab", "gitDir": "test/corpus/repos/javascript", - "sha2": "ed055ea2c0cdae06c2679c7febe33ea291ab50af" + "sha2": "b29aa1c8b4ce011908b5fcb146722a7415615b61" } ,{ "testCaseDescription": "javascript-var-declaration-delete-insert-test", @@ -140,8 +135,7 @@ } ] }, - "summary": "Replaced the 'x' variable with the 'x' variable", - "tag": "JSONSummary" + "summary": "Replaced the 'x' variable with the 'x' variable" }, { "span": { @@ -156,8 +150,7 @@ ] } }, - "summary": "Deleted the 'y' variable", - "tag": "JSONSummary" + "summary": "Deleted the 'y' variable" }, { "span": { @@ -172,8 +165,7 @@ ] } }, - "summary": "Deleted the 'z' variable", - "tag": "JSONSummary" + "summary": "Deleted the 'z' variable" } ] }, @@ -182,9 +174,9 @@ "filePaths": [ "var-declaration.js" ], - "sha1": "ed055ea2c0cdae06c2679c7febe33ea291ab50af", + "sha1": "b29aa1c8b4ce011908b5fcb146722a7415615b61", "gitDir": "test/corpus/repos/javascript", - "sha2": "58c6d08bf25620f6b3be0ce0bde34968aa8731cb" + "sha2": "121898865a4153fdee7af490b7f95e63dfecd245" } ,{ "testCaseDescription": "javascript-var-declaration-replacement-test", @@ -216,8 +208,7 @@ } ] }, - "summary": "Replaced the 'x' variable with the 'x' variable", - "tag": "JSONSummary" + "summary": "Replaced the 'x' variable with the 'x' variable" }, { "span": { @@ -232,8 +223,7 @@ ] } }, - "summary": "Added the 'y' variable", - "tag": "JSONSummary" + "summary": "Added the 'y' variable" }, { "span": { @@ -248,8 +238,7 @@ ] } }, - "summary": "Added the 'z' variable", - "tag": "JSONSummary" + "summary": "Added the 'z' variable" } ] }, @@ -258,9 +247,9 @@ "filePaths": [ "var-declaration.js" ], - "sha1": "58c6d08bf25620f6b3be0ce0bde34968aa8731cb", + "sha1": "121898865a4153fdee7af490b7f95e63dfecd245", "gitDir": "test/corpus/repos/javascript", - "sha2": "b342a171c3b2487402c335c5073c5b3e9a6d9c28" + "sha2": "4f800595767d306adf1001a3e532c0f49c77549b" } ,{ "testCaseDescription": "javascript-var-declaration-delete-replacement-test", @@ -280,8 +269,7 @@ ] } }, - "summary": "Deleted the 'x' variable", - "tag": "JSONSummary" + "summary": "Deleted the 'x' variable" }, { "span": { @@ -296,8 +284,7 @@ ] } }, - "summary": "Deleted the 'y' variable", - "tag": "JSONSummary" + "summary": "Deleted the 'y' variable" }, { "span": { @@ -312,8 +299,7 @@ ] } }, - "summary": "Deleted the 'z' variable", - "tag": "JSONSummary" + "summary": "Deleted the 'z' variable" }, { "span": { @@ -328,8 +314,7 @@ ] } }, - "summary": "Deleted the 'x' variable", - "tag": "JSONSummary" + "summary": "Deleted the 'x' variable" }, { "span": { @@ -344,8 +329,7 @@ ] } }, - "summary": "Added the 'x' variable", - "tag": "JSONSummary" + "summary": "Added the 'x' variable" }, { "span": { @@ -360,8 +344,7 @@ ] } }, - "summary": "Added the 'y' variable", - "tag": "JSONSummary" + "summary": "Added the 'y' variable" }, { "span": { @@ -376,8 +359,7 @@ ] } }, - "summary": "Added the 'z' variable", - "tag": "JSONSummary" + "summary": "Added the 'z' variable" } ] }, @@ -386,9 +368,9 @@ "filePaths": [ "var-declaration.js" ], - "sha1": "b342a171c3b2487402c335c5073c5b3e9a6d9c28", + "sha1": "4f800595767d306adf1001a3e532c0f49c77549b", "gitDir": "test/corpus/repos/javascript", - "sha2": "e7b32730438255bab8de8b0c76f204ef5d5517ec" + "sha2": "a62c5f0ceea3f103315aab7f595f0fc257690f46" } ,{ "testCaseDescription": "javascript-var-declaration-delete-test", @@ -408,8 +390,7 @@ ] } }, - "summary": "Deleted the 'x' variable", - "tag": "JSONSummary" + "summary": "Deleted the 'x' variable" } ] }, @@ -418,9 +399,9 @@ "filePaths": [ "var-declaration.js" ], - "sha1": "e7b32730438255bab8de8b0c76f204ef5d5517ec", + "sha1": "a62c5f0ceea3f103315aab7f595f0fc257690f46", "gitDir": "test/corpus/repos/javascript", - "sha2": "9de9b7db92e589ace7505ab9b4db1c40ec631165" + "sha2": "a1ce7a96169c9034dbc16807e754c5a58df0c0f8" } ,{ "testCaseDescription": "javascript-var-declaration-delete-rest-test", @@ -440,8 +421,7 @@ ] } }, - "summary": "Deleted the 'x' variable", - "tag": "JSONSummary" + "summary": "Deleted the 'x' variable" }, { "span": { @@ -456,8 +436,7 @@ ] } }, - "summary": "Deleted the 'y' variable", - "tag": "JSONSummary" + "summary": "Deleted the 'y' variable" }, { "span": { @@ -472,8 +451,7 @@ ] } }, - "summary": "Deleted the 'z' variable", - "tag": "JSONSummary" + "summary": "Deleted the 'z' variable" } ] }, @@ -482,7 +460,7 @@ "filePaths": [ "var-declaration.js" ], - "sha1": "9de9b7db92e589ace7505ab9b4db1c40ec631165", + "sha1": "a1ce7a96169c9034dbc16807e754c5a58df0c0f8", "gitDir": "test/corpus/repos/javascript", - "sha2": "f3566e32792c678aaed037ccd4998275a9c111f6" + "sha2": "538d0fcee9f9f1163338901d5c7ec3035da370c4" }] diff --git a/test/corpus/diff-summaries/javascript/variable.json b/test/corpus/diff-summaries/javascript/variable.json index 8f6371c24..4ac3183d8 100644 --- a/test/corpus/diff-summaries/javascript/variable.json +++ b/test/corpus/diff-summaries/javascript/variable.json @@ -16,8 +16,7 @@ ] } }, - "summary": "Added the 'theVar' identifier", - "tag": "JSONSummary" + "summary": "Added the 'theVar' identifier" } ] }, @@ -26,9 +25,9 @@ "filePaths": [ "variable.js" ], - "sha1": "2074bb33669e57e62f87e701e4265cf784b19e58", + "sha1": "af7fa2faefa291b9a06977c18ce312bffe7bc871", "gitDir": "test/corpus/repos/javascript", - "sha2": "8b059350148dcffeee8ccd9366ad66c7d1cef915" + "sha2": "60d7f50440d1afcabab62927fc575f4aa29cbac7" } ,{ "testCaseDescription": "javascript-variable-replacement-insert-test", @@ -48,8 +47,7 @@ ] } }, - "summary": "Added the 'theVar2' identifier", - "tag": "JSONSummary" + "summary": "Added the 'theVar2' identifier" }, { "span": { @@ -64,8 +62,7 @@ ] } }, - "summary": "Added the 'theVar' identifier", - "tag": "JSONSummary" + "summary": "Added the 'theVar' identifier" } ] }, @@ -74,9 +71,9 @@ "filePaths": [ "variable.js" ], - "sha1": "8b059350148dcffeee8ccd9366ad66c7d1cef915", + "sha1": "60d7f50440d1afcabab62927fc575f4aa29cbac7", "gitDir": "test/corpus/repos/javascript", - "sha2": "90ab826472b30886ece143bfb81316b6a727943a" + "sha2": "fb6bdcb35d721efd2efc359911854cdd2834eece" } ,{ "testCaseDescription": "javascript-variable-delete-insert-test", @@ -108,8 +105,7 @@ } ] }, - "summary": "Replaced the 'theVar2' identifier with the 'theVar' identifier", - "tag": "JSONSummary" + "summary": "Replaced the 'theVar2' identifier with the 'theVar' identifier" } ] }, @@ -118,9 +114,9 @@ "filePaths": [ "variable.js" ], - "sha1": "90ab826472b30886ece143bfb81316b6a727943a", + "sha1": "fb6bdcb35d721efd2efc359911854cdd2834eece", "gitDir": "test/corpus/repos/javascript", - "sha2": "44ab672853770a8141287a7f6b99064f9138cb77" + "sha2": "b49f639a28f9a64cb9c8994eb626c0353b3b8d34" } ,{ "testCaseDescription": "javascript-variable-replacement-test", @@ -152,8 +148,7 @@ } ] }, - "summary": "Replaced the 'theVar' identifier with the 'theVar2' identifier", - "tag": "JSONSummary" + "summary": "Replaced the 'theVar' identifier with the 'theVar2' identifier" } ] }, @@ -162,9 +157,9 @@ "filePaths": [ "variable.js" ], - "sha1": "44ab672853770a8141287a7f6b99064f9138cb77", + "sha1": "b49f639a28f9a64cb9c8994eb626c0353b3b8d34", "gitDir": "test/corpus/repos/javascript", - "sha2": "5952e6fbb59faeda16dd0ce1ded38dcd90f1b587" + "sha2": "26355d52a696edb7b9cc3fd119c6f5fd6afdd24c" } ,{ "testCaseDescription": "javascript-variable-delete-replacement-test", @@ -184,8 +179,7 @@ ] } }, - "summary": "Deleted the 'theVar2' identifier", - "tag": "JSONSummary" + "summary": "Deleted the 'theVar2' identifier" }, { "span": { @@ -200,8 +194,7 @@ ] } }, - "summary": "Deleted the 'theVar' identifier", - "tag": "JSONSummary" + "summary": "Deleted the 'theVar' identifier" }, { "span": { @@ -216,8 +209,7 @@ ] } }, - "summary": "Added the 'theVar2' identifier", - "tag": "JSONSummary" + "summary": "Added the 'theVar2' identifier" } ] }, @@ -226,9 +218,9 @@ "filePaths": [ "variable.js" ], - "sha1": "5952e6fbb59faeda16dd0ce1ded38dcd90f1b587", + "sha1": "26355d52a696edb7b9cc3fd119c6f5fd6afdd24c", "gitDir": "test/corpus/repos/javascript", - "sha2": "bf907d6d61c4fe246ce406e7fe04f0aafe39782c" + "sha2": "c7eb7e72c8e57e95670f442f9a1129a19a4864bd" } ,{ "testCaseDescription": "javascript-variable-delete-test", @@ -248,8 +240,7 @@ ] } }, - "summary": "Deleted the 'theVar' identifier", - "tag": "JSONSummary" + "summary": "Deleted the 'theVar' identifier" } ] }, @@ -258,9 +249,9 @@ "filePaths": [ "variable.js" ], - "sha1": "bf907d6d61c4fe246ce406e7fe04f0aafe39782c", + "sha1": "c7eb7e72c8e57e95670f442f9a1129a19a4864bd", "gitDir": "test/corpus/repos/javascript", - "sha2": "e044481441f48984c54cab43b37b7a07696be1c8" + "sha2": "3d7a287fb605880675b46eba44ecfaab86e8ba35" } ,{ "testCaseDescription": "javascript-variable-delete-rest-test", @@ -280,8 +271,7 @@ ] } }, - "summary": "Deleted the 'theVar2' identifier", - "tag": "JSONSummary" + "summary": "Deleted the 'theVar2' identifier" } ] }, @@ -290,7 +280,7 @@ "filePaths": [ "variable.js" ], - "sha1": "e044481441f48984c54cab43b37b7a07696be1c8", + "sha1": "3d7a287fb605880675b46eba44ecfaab86e8ba35", "gitDir": "test/corpus/repos/javascript", - "sha2": "1ecef9aa25c5f5b2d024632f76333266bbaa3b08" + "sha2": "7ad1f0f1e9c4fda88ae65caff85d855f6b429c0f" }] diff --git a/test/corpus/diff-summaries/javascript/void-operator.json b/test/corpus/diff-summaries/javascript/void-operator.json index 43f87d633..b9b993da2 100644 --- a/test/corpus/diff-summaries/javascript/void-operator.json +++ b/test/corpus/diff-summaries/javascript/void-operator.json @@ -16,8 +16,7 @@ ] } }, - "summary": "Added the 'void b()' operator", - "tag": "JSONSummary" + "summary": "Added the 'void b()' operator" } ] }, @@ -26,9 +25,9 @@ "filePaths": [ "void-operator.js" ], - "sha1": "a34d26b577d45eb717e1fe5106677325581d96fb", + "sha1": "7ba29898c7f45897e7de7f1191e0c6b7f9fac35e", "gitDir": "test/corpus/repos/javascript", - "sha2": "509b527807b92bc977ea4d76352167537a31e59a" + "sha2": "04efcf66ddcaa70558821725988f42c1af11f3cc" } ,{ "testCaseDescription": "javascript-void-operator-replacement-insert-test", @@ -48,8 +47,7 @@ ] } }, - "summary": "Added the 'void c()' operator", - "tag": "JSONSummary" + "summary": "Added the 'void c()' operator" }, { "span": { @@ -64,8 +62,7 @@ ] } }, - "summary": "Added the 'void b()' operator", - "tag": "JSONSummary" + "summary": "Added the 'void b()' operator" } ] }, @@ -74,9 +71,9 @@ "filePaths": [ "void-operator.js" ], - "sha1": "509b527807b92bc977ea4d76352167537a31e59a", + "sha1": "04efcf66ddcaa70558821725988f42c1af11f3cc", "gitDir": "test/corpus/repos/javascript", - "sha2": "94643283de3ca9031814c2686d6981d061ea39e5" + "sha2": "2cfcfeb87a2b4a0db7905bc74d3a7e1be38cbf5a" } ,{ "testCaseDescription": "javascript-void-operator-delete-insert-test", @@ -108,8 +105,7 @@ } ] }, - "summary": "Replaced the 'c' identifier with the 'b' identifier in the b() function call", - "tag": "JSONSummary" + "summary": "Replaced the 'c' identifier with the 'b' identifier in the b() function call" } ] }, @@ -118,9 +114,9 @@ "filePaths": [ "void-operator.js" ], - "sha1": "94643283de3ca9031814c2686d6981d061ea39e5", + "sha1": "2cfcfeb87a2b4a0db7905bc74d3a7e1be38cbf5a", "gitDir": "test/corpus/repos/javascript", - "sha2": "da299cf12b29b9a9e4c160c899a5a99f775db019" + "sha2": "cd22e88db42b827ae56fb6ca9edeb221c67f038d" } ,{ "testCaseDescription": "javascript-void-operator-replacement-test", @@ -152,8 +148,7 @@ } ] }, - "summary": "Replaced the 'b' identifier with the 'c' identifier in the c() function call", - "tag": "JSONSummary" + "summary": "Replaced the 'b' identifier with the 'c' identifier in the c() function call" } ] }, @@ -162,9 +157,9 @@ "filePaths": [ "void-operator.js" ], - "sha1": "da299cf12b29b9a9e4c160c899a5a99f775db019", + "sha1": "cd22e88db42b827ae56fb6ca9edeb221c67f038d", "gitDir": "test/corpus/repos/javascript", - "sha2": "f7257d8cc48c28fa362ac35b2ffe8a289ccda5b3" + "sha2": "0b81ec59795d14187d78eb1f48b8b5e8acb0c748" } ,{ "testCaseDescription": "javascript-void-operator-delete-replacement-test", @@ -184,8 +179,7 @@ ] } }, - "summary": "Deleted the 'void c()' operator", - "tag": "JSONSummary" + "summary": "Deleted the 'void c()' operator" }, { "span": { @@ -200,8 +194,7 @@ ] } }, - "summary": "Deleted the 'void b()' operator", - "tag": "JSONSummary" + "summary": "Deleted the 'void b()' operator" }, { "span": { @@ -216,8 +209,7 @@ ] } }, - "summary": "Added the 'void c()' operator", - "tag": "JSONSummary" + "summary": "Added the 'void c()' operator" } ] }, @@ -226,9 +218,9 @@ "filePaths": [ "void-operator.js" ], - "sha1": "f7257d8cc48c28fa362ac35b2ffe8a289ccda5b3", + "sha1": "0b81ec59795d14187d78eb1f48b8b5e8acb0c748", "gitDir": "test/corpus/repos/javascript", - "sha2": "eba77c9ca2f30769e008be446ac51602d8774949" + "sha2": "9860d6a2ad25819e82ac0848010b5d6f7e1b5b76" } ,{ "testCaseDescription": "javascript-void-operator-delete-test", @@ -248,8 +240,7 @@ ] } }, - "summary": "Deleted the 'void b()' operator", - "tag": "JSONSummary" + "summary": "Deleted the 'void b()' operator" } ] }, @@ -258,9 +249,9 @@ "filePaths": [ "void-operator.js" ], - "sha1": "eba77c9ca2f30769e008be446ac51602d8774949", + "sha1": "9860d6a2ad25819e82ac0848010b5d6f7e1b5b76", "gitDir": "test/corpus/repos/javascript", - "sha2": "e2d838d6c0797077d1197573fcb31dab223f299b" + "sha2": "df7dcb8b1dbc8cd8d7044c0ea75c825e95f55279" } ,{ "testCaseDescription": "javascript-void-operator-delete-rest-test", @@ -280,8 +271,7 @@ ] } }, - "summary": "Deleted the 'void c()' operator", - "tag": "JSONSummary" + "summary": "Deleted the 'void c()' operator" } ] }, @@ -290,7 +280,7 @@ "filePaths": [ "void-operator.js" ], - "sha1": "e2d838d6c0797077d1197573fcb31dab223f299b", + "sha1": "df7dcb8b1dbc8cd8d7044c0ea75c825e95f55279", "gitDir": "test/corpus/repos/javascript", - "sha2": "f79e1375ce21269c7d54de075cbed5f40ea1b501" + "sha2": "85ef535e2b1570133c3be4bddaffc8513555ad2c" }] diff --git a/test/corpus/diff-summaries/javascript/while-statement.json b/test/corpus/diff-summaries/javascript/while-statement.json index a81fc6bd3..9b990e54c 100644 --- a/test/corpus/diff-summaries/javascript/while-statement.json +++ b/test/corpus/diff-summaries/javascript/while-statement.json @@ -16,8 +16,7 @@ ] } }, - "summary": "Added the 'a' while statement", - "tag": "JSONSummary" + "summary": "Added the 'a' while statement" } ] }, @@ -26,9 +25,9 @@ "filePaths": [ "while-statement.js" ], - "sha1": "126641b1c820ff0a55da55b367554ff1698a4fc3", + "sha1": "1476b59a288eafecf5ddd48696a3e207754a9668", "gitDir": "test/corpus/repos/javascript", - "sha2": "9c434e0c6b44a4e60ca5b0bed09dbaef6224bc86" + "sha2": "f23284bfe8af3aeae4cd0de9ff318f5c0bb1117a" } ,{ "testCaseDescription": "javascript-while-statement-replacement-insert-test", @@ -48,8 +47,7 @@ ] } }, - "summary": "Added the 'b' while statement", - "tag": "JSONSummary" + "summary": "Added the 'b' while statement" }, { "span": { @@ -64,8 +62,7 @@ ] } }, - "summary": "Added the 'a' while statement", - "tag": "JSONSummary" + "summary": "Added the 'a' while statement" } ] }, @@ -74,9 +71,9 @@ "filePaths": [ "while-statement.js" ], - "sha1": "9c434e0c6b44a4e60ca5b0bed09dbaef6224bc86", + "sha1": "f23284bfe8af3aeae4cd0de9ff318f5c0bb1117a", "gitDir": "test/corpus/repos/javascript", - "sha2": "0c64c82fc19f9a9f7598962e6a629eda732414c4" + "sha2": "0187cf96aade757c54df567264bce2b15c5d2bde" } ,{ "testCaseDescription": "javascript-while-statement-delete-insert-test", @@ -108,8 +105,7 @@ } ] }, - "summary": "Replaced the 'b' identifier with the 'a' identifier", - "tag": "JSONSummary" + "summary": "Replaced the 'b' identifier with the 'a' identifier" }, { "span": { @@ -136,8 +132,7 @@ } ] }, - "summary": "Replaced the 'a' identifier with the 'b' identifier in the b() function call", - "tag": "JSONSummary" + "summary": "Replaced the 'a' identifier with the 'b' identifier in the b() function call" } ] }, @@ -146,9 +141,9 @@ "filePaths": [ "while-statement.js" ], - "sha1": "0c64c82fc19f9a9f7598962e6a629eda732414c4", + "sha1": "0187cf96aade757c54df567264bce2b15c5d2bde", "gitDir": "test/corpus/repos/javascript", - "sha2": "ebc38db083a37927879c8a7896d84c6ad670bd41" + "sha2": "ea3cd5cf3a270d94a6fb64540f5d15c3a862d7db" } ,{ "testCaseDescription": "javascript-while-statement-replacement-test", @@ -180,8 +175,7 @@ } ] }, - "summary": "Replaced the 'a' identifier with the 'b' identifier", - "tag": "JSONSummary" + "summary": "Replaced the 'a' identifier with the 'b' identifier" }, { "span": { @@ -208,8 +202,7 @@ } ] }, - "summary": "Replaced the 'b' identifier with the 'a' identifier in the a() function call", - "tag": "JSONSummary" + "summary": "Replaced the 'b' identifier with the 'a' identifier in the a() function call" } ] }, @@ -218,9 +211,9 @@ "filePaths": [ "while-statement.js" ], - "sha1": "ebc38db083a37927879c8a7896d84c6ad670bd41", + "sha1": "ea3cd5cf3a270d94a6fb64540f5d15c3a862d7db", "gitDir": "test/corpus/repos/javascript", - "sha2": "a2a000e2b77ba785dc25df73cc387a4fff5fd6ce" + "sha2": "201605c6796eb154347d09577ba30c428ff8a2fe" } ,{ "testCaseDescription": "javascript-while-statement-delete-replacement-test", @@ -240,8 +233,7 @@ ] } }, - "summary": "Deleted the 'b' while statement", - "tag": "JSONSummary" + "summary": "Deleted the 'b' while statement" }, { "span": { @@ -256,8 +248,7 @@ ] } }, - "summary": "Deleted the 'a' while statement", - "tag": "JSONSummary" + "summary": "Deleted the 'a' while statement" }, { "span": { @@ -272,8 +263,7 @@ ] } }, - "summary": "Added the 'b' while statement", - "tag": "JSONSummary" + "summary": "Added the 'b' while statement" } ] }, @@ -282,9 +272,9 @@ "filePaths": [ "while-statement.js" ], - "sha1": "a2a000e2b77ba785dc25df73cc387a4fff5fd6ce", + "sha1": "201605c6796eb154347d09577ba30c428ff8a2fe", "gitDir": "test/corpus/repos/javascript", - "sha2": "1766bc7de3028114c029d58d8dad57d1b224b56f" + "sha2": "b6a9d4096d663c0a0095d75e9ceb4dacf5bbee39" } ,{ "testCaseDescription": "javascript-while-statement-delete-test", @@ -304,8 +294,7 @@ ] } }, - "summary": "Deleted the 'a' while statement", - "tag": "JSONSummary" + "summary": "Deleted the 'a' while statement" } ] }, @@ -314,9 +303,9 @@ "filePaths": [ "while-statement.js" ], - "sha1": "1766bc7de3028114c029d58d8dad57d1b224b56f", + "sha1": "b6a9d4096d663c0a0095d75e9ceb4dacf5bbee39", "gitDir": "test/corpus/repos/javascript", - "sha2": "7acae0fbb45845daa0c4054e20d30aff3f37b872" + "sha2": "a82434bad4b9b59f0d6df675bc4fadfa97b992b4" } ,{ "testCaseDescription": "javascript-while-statement-delete-rest-test", @@ -336,8 +325,7 @@ ] } }, - "summary": "Deleted the 'b' while statement", - "tag": "JSONSummary" + "summary": "Deleted the 'b' while statement" } ] }, @@ -346,7 +334,7 @@ "filePaths": [ "while-statement.js" ], - "sha1": "7acae0fbb45845daa0c4054e20d30aff3f37b872", + "sha1": "a82434bad4b9b59f0d6df675bc4fadfa97b992b4", "gitDir": "test/corpus/repos/javascript", - "sha2": "ae76dbf085fd365417c914186052f77fec683519" + "sha2": "ff624cef881f79c1f5e43043657a490eb7d137e2" }] diff --git a/test/corpus/repos/javascript b/test/corpus/repos/javascript index a1ec5326a..dce5b472e 160000 --- a/test/corpus/repos/javascript +++ b/test/corpus/repos/javascript @@ -1 +1 @@ -Subproject commit a1ec5326a248592c7deb7a7e3b3ece00b97506bb +Subproject commit dce5b472e5bcc43861e65b412644c7931f12d313